Ignore:
Timestamp:
Jul 23, 2016, 7:45:38 AM (8 years ago)
Author:
Ehouarn Millour
Message:

Cleanup in the dynamics: turn comvert.h into module comvert_mod.F90
EM

Location:
LMDZ5/trunk/libf/dyn3dpar
Files:
34 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dpar/advect_new_p.F

    r2597 r2600  
    2929#include "dimensions.h"
    3030#include "paramet.h"
    31 #include "comvert.h"
    3231#include "comgeom.h"
    3332#include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/advect_p.F

    r2597 r2600  
    2828#include "dimensions.h"
    2929#include "paramet.h"
    30 #include "comvert.h"
    3130#include "comgeom.h"
    3231#include "logic.h"
     
    8685                 
    8786           uav(ij,l)=0.25*(ucov(ij,l)+ucov(ij-iip1,l))
    88      .               +0.25*(ucov(ij+iip1,l)+ucov(ij,l))
     87     .                     +0.25*(ucov(ij+iip1,l)+ucov(ij,l))
    8988         ENDDO
    9089         
  • LMDZ5/trunk/libf/dyn3dpar/advtrac_p.F90

    r2597 r2600  
    2424  include "dimensions.h"
    2525  include "paramet.h"
    26   include "comvert.h"
    2726  include "comdissip.h"
    2827  include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3dpar/bilan_dyn_p.F

    r2597 r2600  
    1818      use write_field_p
    1919      USE comconst_mod, ONLY: cpp, pi
     20      USE comvert_mod, ONLY: presnivs
     21     
    2022      IMPLICIT NONE
    2123
    2224#include "dimensions.h"
    2325#include "paramet.h"
    24 #include "comvert.h"
    2526#include "comgeom2.h"
    2627#include "temps.h"
     
    202203
    203204!        if (i_sortie.eq.1) then
    204 !        file='dynzon'
     205!        file='dynzon'
    205206!         if (mpi_rank==0) then
    206 !        call inigrads(ifile,1
     207!        call inigrads(ifile,1
    207208!     s  ,0.,180./pi,0.,0.,jjm,rlatv,-90.,90.,180./pi
    208209!     s  ,llm,presnivs,1.
     
    568569        do l=1,llm
    569570          Q_cum(:,jjb:jje,l,iQ)=Q_cum(:,jjb:jje,l,iQ)
    570      .                          /masse_cum(:,jjb:jje,l)
     571     .                                /masse_cum(:,jjb:jje,l)
    571572        enddo
    572573!$OMP ENDDO NOWAIT
  • LMDZ5/trunk/libf/dyn3dpar/caldyn_p.F

    r2597 r2600  
    1010      USE parallel_lmdz
    1111      USE Write_Field_p
     12      USE comvert_mod, ONLY: ap, bp
    1213     
    1314      IMPLICIT NONE
     
    3132#include "dimensions.h"
    3233#include "paramet.h"
    33 #include "comvert.h"
    3434#include "comgeom.h"
    3535
  • LMDZ5/trunk/libf/dyn3dpar/convmas1_p.F

    r1907 r2600  
    3232#include "dimensions.h"
    3333#include "paramet.h"
    34 #include "comvert.h"
    3534#include "logic.h"
    3635
  • LMDZ5/trunk/libf/dyn3dpar/convmas2_p.F

    r1907 r2600  
    3232#include "dimensions.h"
    3333#include "paramet.h"
    34 #include "comvert.h"
    3534#include "logic.h"
    3635
  • LMDZ5/trunk/libf/dyn3dpar/convmas_p.F

    r1907 r2600  
    3232#include "dimensions.h"
    3333#include "paramet.h"
    34 #include "comvert.h"
    3534#include "logic.h"
    3635
  • LMDZ5/trunk/libf/dyn3dpar/dudv2_p.F

    r1907 r2600  
    2525#include "dimensions.h"
    2626#include "paramet.h"
    27 #include "comvert.h"
    2827
    2928      REAL teta( ip1jmp1,llm ),pkf( ip1jmp1,llm ) ,bern( ip1jmp1,llm ),
  • LMDZ5/trunk/libf/dyn3dpar/dynetat0.F

    r2598 r2600  
    99
    1010      use control_mod, only : planet_type
     11      USE comvert_mod, ONLY: pa,preff
    1112      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, im, jm, kappa,
    1213     &                        lllm, omeg, rad
     14
    1315      USE serre_mod, ONLY: clon,clat,grossismx,grossismy
    1416
     
    3335#include "paramet.h"
    3436#include "temps.h"
    35 #include "comvert.h"
    3637#include "comgeom2.h"
    3738#include "ener.h"
  • LMDZ5/trunk/libf/dyn3dpar/dynredem.F

    r2598 r2600  
    99      USE infotrac
    1010      use netcdf95, only: NF95_PUT_VAR
     11      USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,pa,preff,
     12     &                        nivsig,nivsigs
    1113      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
    1214      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
     
    2123#include "dimensions.h"
    2224#include "paramet.h"
    23 #include "comvert.h"
    2425#include "comgeom2.h"
    2526#include "temps.h"
     
    481482#include "description.h"
    482483#include "netcdf.inc"
    483 #include "comvert.h"
    484484#include "comgeom.h"
    485485#include "temps.h"
  • LMDZ5/trunk/libf/dyn3dpar/dynredem_p.F

    r2598 r2600  
    1010      USE infotrac
    1111      use netcdf95, only: NF95_PUT_VAR
     12      USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,pa,preff,
     13     &                        nivsig,nivsigs
    1214      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
    1315      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
     
    2224#include "dimensions.h"
    2325#include "paramet.h"
    24 #include "comvert.h"
    2526#include "comgeom2.h"
    2627#include "temps.h"
     
    482483#include "description.h"
    483484#include "netcdf.inc"
    484 #include "comvert.h"
    485485#include "comgeom.h"
    486486#include "temps.h"
  • LMDZ5/trunk/libf/dyn3dpar/exner_hyb_p_m.F90

    r2598 r2600  
    3434    USE parallel_lmdz
    3535    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
     36    USE comvert_mod, ONLY: preff
    3637    !
    3738    include "dimensions.h"
    3839    include "paramet.h"
    3940    include "comgeom.h"
    40     include "comvert.h"
    4141
    4242    INTEGER  ngrid
  • LMDZ5/trunk/libf/dyn3dpar/exner_milieu_p_m.F90

    r2598 r2600  
    3131    USE parallel_lmdz
    3232    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
     33    USE comvert_mod, ONLY: preff
    3334    !
    3435    include "dimensions.h"
    3536    include "paramet.h"
    3637    include "comgeom.h"
    37     include "comvert.h"
    3838
    3939    INTEGER  ngrid
  • LMDZ5/trunk/libf/dyn3dpar/fluxstokenc_p.F

    r2597 r2600  
    2121#include "dimensions.h"
    2222#include "paramet.h"
    23 #include "comvert.h"
    2423#include "comgeom.h"
    2524#include "tracstoke.h"
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r2598 r2600  
    6868#include "paramet.h"
    6969#include "comdissnew.h"
    70 #include "comvert.h"
    7170#include "comgeom.h"
    7271#include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/geopot_p.F

    r1907 r2600  
    2828#include "dimensions.h"
    2929#include "paramet.h"
    30 #include "comvert.h"
    3130
    3231c   Arguments:
  • LMDZ5/trunk/libf/dyn3dpar/groupe_p.F

    r2597 r2600  
    1818#include "paramet.h"
    1919#include "comgeom2.h"
    20 #include "comvert.h"
    2120
    2221!     integer ngroup
  • LMDZ5/trunk/libf/dyn3dpar/guide_p_mod.F90

    r2598 r2600  
    340340    USE control_mod
    341341    USE comconst_mod, ONLY: daysec, dtvr, cpp, kappa
     342    USE comvert_mod, ONLY: ap, bp, preff, presnivs, pressure_exner
    342343   
    343344    IMPLICIT NONE
     
    345346    INCLUDE "dimensions.h"
    346347    INCLUDE "paramet.h"
    347     INCLUDE "comvert.h"
    348348
    349349    ! Variables entree
     
    707707  USE Bands
    708708  USE comconst_mod, ONLY: cpp, kappa
     709  USE comvert_mod, ONLY: preff, pressure_exner, bp, ap
    709710  IMPLICIT NONE
    710711
    711712  include "dimensions.h"
    712713  include "paramet.h"
    713   include "comvert.h"
    714714  include "comgeom2.h"
    715715
     
    18141814    USE parallel_lmdz
    18151815    USE comconst_mod, ONLY: pi
     1816    USE comvert_mod, ONLY: presnivs
    18161817    IMPLICIT NONE
    18171818
     
    18201821    INCLUDE "netcdf.inc"
    18211822    INCLUDE "comgeom2.h"
    1822     INCLUDE "comvert.h"
    18231823   
    18241824    ! Variables entree
  • LMDZ5/trunk/libf/dyn3dpar/iniacademic.F90

    r2597 r2600  
    1717  use exner_milieu_m, only: exner_milieu
    1818  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
     19  USE comvert_mod, ONLY: ap, bp, preff, presnivs, pressure_exner
    1920
    2021  !   Author:    Frederic Hourdin      original: 15/01/93
     
    2930  include "dimensions.h"
    3031  include "paramet.h"
    31   include "comvert.h"
    3232  include "comgeom.h"
    3333  include "academic.h"
  • LMDZ5/trunk/libf/dyn3dpar/initdynav_p.F

    r2598 r2600  
    1313       USE infotrac
    1414       USE comconst_mod, ONLY: pi
     15       USE comvert_mod, ONLY: nivsigs
    1516
    1617      implicit none
     
    4445#include "dimensions.h"
    4546#include "paramet.h"
    46 #include "comvert.h"
    4747#include "comgeom.h"
    4848#include "temps.h"
  • LMDZ5/trunk/libf/dyn3dpar/initfluxsto_p.F

    r2598 r2600  
    1414       use misc_mod
    1515       USE comconst_mod, ONLY: pi
     16       USE comvert_mod, ONLY: nivsigs
    1617       
    1718      implicit none
     
    4647#include "dimensions.h"
    4748#include "paramet.h"
    48 #include "comvert.h"
    4949#include "comgeom.h"
    5050#include "temps.h"
     
    105105      CALL ymds2ju(zan, 1, idayref, 0.0, zjulian)
    106106      tau0 = itau_dyn
    107        
    108         do jj = 1, jjp1
     107       
     108        do jj = 1, jjp1
    109109        do ii = 1, iip1
    110110          rlong(ii,jj) = rlonu(ii) * 180. / pi
     
    164164     .             1, iip1, 1, jjn,tau0, zjulian, tstep, vhoriid,
    165165     .             filevid,dynv_domain_id)
    166        
    167       rl(1,1) = 1.     
     166       
     167      rl(1,1) = 1.       
    168168     
    169169      if (mpi_rank==0) then
     
    190190      call histhori(fileid, iip1, rlong(:,jjb:jje),jjn,rlat(:,jjb:jje),
    191191     .             'scalar','Grille points scalaires', thoriid)
    192        
     192       
    193193C
    194194C  Appel a histvert pour la grille verticale
     
    210210C
    211211C  Appels a histdef pour la definition des variables a sauvegarder
    212        
    213         CALL histdef(fileid, "phis", "Surface geop. height", "-",
     212       
     213        CALL histdef(fileid, "phis", "Surface geop. height", "-",
    214214     .                iip1,jjn,thoriid, 1,1,1, -99, 32,
    215215     .                "once", t_ops, t_wrt)
     
    218218     .                iip1,jjn,thoriid, 1,1,1, -99, 32,
    219219     .                "once", t_ops, t_wrt)
    220        
     220       
    221221        if (mpi_rank==0) then
    222        
    223         CALL histdef(filedid, "dtvr", "tps dyn", "s",
     222       
     223        CALL histdef(filedid, "dtvr", "tps dyn", "s",
    224224     .                1,1,dhoriid, 1,1,1, -99, 32,
    225225     .                "once", t_ops, t_wrt)
     
    288288        if (mpi_rank==0) call histsync(filedid)
    289289      endif
    290        
     290       
    291291#else
    292292      write(lunout,*)'initfluxsto_p: Needs IOIPSL to function'
  • LMDZ5/trunk/libf/dyn3dpar/inithist_p.F

    r2598 r2600  
    1414       USE infotrac
    1515       USE comconst_mod, ONLY: pi
     16       USE comvert_mod, ONLY: nivsigs
    1617
    1718      implicit none
     
    4647#include "dimensions.h"
    4748#include "paramet.h"
    48 #include "comvert.h"
    4949#include "comgeom.h"
    5050#include "temps.h"
  • LMDZ5/trunk/libf/dyn3dpar/integrd_p.F

    r2598 r2600  
    88      USE control_mod, only : planet_type
    99      USE comconst_mod, ONLY: pi
     10      USE comvert_mod, ONLY: ap, bp
    1011      IMPLICIT NONE
    1112
     
    2930#include "paramet.h"
    3031#include "comgeom.h"
    31 #include "comvert.h"
    3232#include "logic.h"
    3333#include "temps.h"
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r2598 r2600  
    2828     &                       periodav, ok_dyn_ave, output_grads_dyn,
    2929     &                       iapp_tracvl
     30       USE comvert_mod, ONLY: ap,bp,pressure_exner,presnivs
    3031       USE comconst_mod, ONLY: cpp, dtvr, ihf, dtphys, pi, jmp1
    3132      IMPLICIT NONE
     
    6566#include "paramet.h"
    6667#include "comdissnew.h"
    67 #include "comvert.h"
    6868#include "comgeom.h"
    6969#include "logic.h"
     
    14541454                call Gather_Field(teta,ip1jmp1,llm,0)
    14551455                call Gather_Field(pk,ip1jmp1,llm,0)
    1456                 call Gather_Field(phi,ip1jmp1,llm,0)
     1456                call Gather_Field(phi,ip1jmp1,llm,0)
    14571457                do iq=1,nqtot
    14581458                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    14591459                enddo
    1460                 call Gather_Field(masse,ip1jmp1,llm,0)
     1460                call Gather_Field(masse,ip1jmp1,llm,0)
    14611461                call Gather_Field(ps,ip1jmp1,1,0)
    1462                 call Gather_Field(phis,ip1jmp1,1,0)
     1462                call Gather_Field(phis,ip1jmp1,1,0)
    14631463                if (mpi_rank==0) then
    14641464                 CALL writedynav(itau,vcov,
    14651465     &                 ucov,teta,pk,phi,q,masse,ps,phis)
    1466                 endif
     1466                endif
    14671467#endif
    14681468!$OMP END MASTER
     
    14761476            IF( MOD(itau,iecri).EQ.0) THEN
    14771477             ! Ehouarn: output only during LF or Backward Matsuno
    1478              if (leapf.or.(.not.leapf.and.(.not.forward))) then
     1478             if (leapf.or.(.not.leapf.and.(.not.forward))) then
    14791479c$OMP BARRIER
    14801480c$OMP MASTER
     
    15141514                call Gather_Field(ucov,ip1jmp1,llm,0)
    15151515                call Gather_Field(teta,ip1jmp1,llm,0)
    1516                 call Gather_Field(phi,ip1jmp1,llm,0)
     1516                call Gather_Field(phi,ip1jmp1,llm,0)
    15171517                do iq=1,nqtot
    15181518                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    15191519                enddo
    1520                 call Gather_Field(masse,ip1jmp1,llm,0)
     1520                call Gather_Field(masse,ip1jmp1,llm,0)
    15211521                call Gather_Field(ps,ip1jmp1,1,0)
    1522                 call Gather_Field(phis,ip1jmp1,1,0)
     1522                call Gather_Field(phis,ip1jmp1,1,0)
    15231523                if (mpi_rank==0) then
    1524                  CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
    1525                 endif
     1524                 CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
     1525                endif
    15261526!              CALL writehist_p(histid,histvid, itau,vcov,
    15271527!     &                         ucov,teta,phi,q,masse,ps,phis)
     
    16491649                call Gather_Field(teta,ip1jmp1,llm,0)
    16501650                call Gather_Field(pk,ip1jmp1,llm,0)
    1651                 call Gather_Field(phi,ip1jmp1,llm,0)
     1651                call Gather_Field(phi,ip1jmp1,llm,0)
    16521652                do iq=1,nqtot
    16531653                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    16541654                enddo
    1655                 call Gather_Field(masse,ip1jmp1,llm,0)
     1655                call Gather_Field(masse,ip1jmp1,llm,0)
    16561656                call Gather_Field(ps,ip1jmp1,1,0)
    1657                 call Gather_Field(phis,ip1jmp1,1,0)
     1657                call Gather_Field(phis,ip1jmp1,1,0)
    16581658                if (mpi_rank==0) then
    16591659                 CALL writedynav(itau,vcov,
    16601660     &                 ucov,teta,pk,phi,q,masse,ps,phis)
    1661                 endif
     1661                endif
    16621662#endif
    16631663!$OMP END MASTER
     
    17051705                call Gather_Field(ucov,ip1jmp1,llm,0)
    17061706                call Gather_Field(teta,ip1jmp1,llm,0)
    1707                 call Gather_Field(phi,ip1jmp1,llm,0)
     1707                call Gather_Field(phi,ip1jmp1,llm,0)
    17081708                do iq=1,nqtot
    17091709                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    17101710                enddo
    1711                 call Gather_Field(masse,ip1jmp1,llm,0)
     1711                call Gather_Field(masse,ip1jmp1,llm,0)
    17121712                call Gather_Field(ps,ip1jmp1,1,0)
    1713                 call Gather_Field(phis,ip1jmp1,1,0)
     1713                call Gather_Field(phis,ip1jmp1,1,0)
    17141714                if (mpi_rank==0) then
    17151715                 CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
    1716                 endif
     1716                endif
    17171717!                CALL writehist_p(histid, histvid, itau,vcov ,
    17181718!     &                           ucov,teta,phi,q,masse,ps,phis)
  • LMDZ5/trunk/libf/dyn3dpar/qminimum_p.F

    r1907 r2600  
    88#include "dimensions.h"
    99#include "paramet.h"
    10 #include "comvert.h"
    1110c
    1211      INTEGER nq
  • LMDZ5/trunk/libf/dyn3dpar/sw_case_williamson91_6.F

    r2597 r2600  
    2727c=======================================================================
    2828      USE comconst_mod, ONLY: cpp, omeg, rad
     29      USE comvert_mod, ONLY: ap, bp, preff
     30     
    2931      IMPLICIT NONE
    3032c-----------------------------------------------------------------------
     
    3436#include "dimensions.h"
    3537#include "paramet.h"
    36 #include "comvert.h"
    3738#include "comgeom.h"
    3839#include "iniprint.h"
  • LMDZ5/trunk/libf/dyn3dpar/top_bound_p.F

    r2597 r2600  
    66      USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound,
    77     &                        tau_top_bound
     8      USE comvert_mod, ONLY: presnivs, preff, scaleheight
     9     
    810      IMPLICIT NONE
    911c
    1012#include "dimensions.h"
    1113#include "paramet.h"
    12 #include "comvert.h"
    1314#include "comgeom2.h"
    1415
     
    7071      REAL uzon(jjp1,llm),vzon(jjm,llm),tzon(jjp1,llm)
    7172     
    72       integer i 
     73      integer i
    7374      REAL,SAVE :: rdamp(llm) ! quenching coefficient
    7475      real,save :: lambda(llm) ! inverse or quenching time scale (Hz)
  • LMDZ5/trunk/libf/dyn3dpar/vitvert_p.F

    r1907 r2600  
    22c
    33      USE parallel_lmdz
     4      USE comvert_mod, ONLY: bp
     5     
    46      IMPLICIT NONE
    57
     
    2830#include "dimensions.h"
    2931#include "paramet.h"
    30 #include "comvert.h"
    3132
    3233      REAL w(ip1jmp1,llm),convm(ip1jmp1,llm)
  • LMDZ5/trunk/libf/dyn3dpar/vlsplt_p.F

    r2597 r2600  
    2626#include "paramet.h"
    2727#include "logic.h"
    28 #include "comvert.h"
    2928
    3029c
     
    208207#include "paramet.h"
    209208#include "logic.h"
    210 #include "comvert.h"
    211209c
    212210c
     
    543541#include "paramet.h"
    544542#include "logic.h"
    545 #include "comvert.h"
    546543#include "comgeom.h"
    547544c
     
    931928#include "paramet.h"
    932929#include "logic.h"
    933 #include "comvert.h"
    934930c
    935931c
  • LMDZ5/trunk/libf/dyn3dpar/vlspltgen_p.F

    r2597 r2600  
    3434#include "paramet.h"
    3535#include "logic.h"
    36 #include "comvert.h"
    3736
    3837c
     
    105104
    106105       
    107         ijb=ij_begin-iip1
    108         ije=ij_end+iip1
    109         if (pole_nord) ijb=ij_begin
    110         if (pole_sud) ije=ij_end
    111        
     106        ijb=ij_begin-iip1
     107        ije=ij_end+iip1
     108        if (pole_nord) ijb=ij_begin
     109        if (pole_sud) ije=ij_end
     110       
    112111c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    113         DO l = 1, llm
     112        DO l = 1, llm
    114113         DO ij = ijb, ije
    115114          tempe(ij) = teta(ij,l) * pk(ij,l) /cpp
     
    191190
    192191        if(iadv(iq) == 0) then
    193        
    194           cycle
    195        
    196         else if (iadv(iq)==10) then
     192       
     193          cycle
     194       
     195        else if (iadv(iq)==10) then
    197196
    198197#ifdef _ADV_HALO       
    199           call vlx_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,
    200      &               ij_begin,ij_begin+2*iip1-1)
     198          call vlx_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,
     199     &                     ij_begin,ij_begin+2*iip1-1)
    201200          call vlx_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,
    202201     &               ij_end-2*iip1+1,ij_end)
    203202#else
    204           call vlx_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,
    205      &               ij_begin,ij_end)
     203          call vlx_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,
     204     &                     ij_begin,ij_end)
    206205#endif
    207206
     
    215214          call VTe(VTHallo)
    216215c$OMP END MASTER
    217         else if (iadv(iq)==14) then
     216        else if (iadv(iq)==14) then
    218217
    219218#ifdef _ADV_HALO           
     
    239238c$OMP END MASTER
    240239        else
    241        
    242           stop 'vlspltgen_p : schema non parallelise'
     240       
     241          stop 'vlspltgen_p : schema non parallelise'
    243242     
    244243        endif
     
    261260
    262261        if(iadv(iq) == 0) then
    263        
    264           cycle
    265        
    266         else if (iadv(iq)==10) then
     262       
     263          cycle
     264       
     265        else if (iadv(iq)==10) then
    267266
    268267#ifdef _ADV_HALLO
     
    270269     &               ij_begin+2*iip1,ij_end-2*iip1)
    271270#endif       
    272         else if (iadv(iq)==14) then
     271        else if (iadv(iq)==14) then
    273272#ifdef _ADV_HALLO
    274273          call vlxqs_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,qsat,
     
    276275#endif   
    277276        else
    278        
    279           stop 'vlspltgen_p : schema non parallelise'
     277       
     278          stop 'vlspltgen_p : schema non parallelise'
    280279     
    281280        endif
     
    301300
    302301        if(iadv(iq) == 0) then
    303        
    304           cycle
    305        
    306         else if (iadv(iq)==10) then
     302       
     303          cycle
     304       
     305        else if (iadv(iq)==10) then
    307306       
    308307          call vly_p(zq(1,1,iq),pente_max,zm(1,1,iq),mv)
    309308 
    310         else if (iadv(iq)==14) then
     309        else if (iadv(iq)==14) then
    311310     
    312311          call vlyqs_p(zq(1,1,iq),pente_max,zm(1,1,iq),mv,qsat)
    313312 
    314313        else
    315        
    316           stop 'vlspltgen_p : schema non parallelise'
     314       
     315          stop 'vlspltgen_p : schema non parallelise'
    317316     
    318317        endif
     
    324323
    325324        if(iadv(iq) == 0) then
    326          
    327           cycle
    328        
    329         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
     325         
     326          cycle
     327       
     328        else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
    330329
    331330c$OMP BARRIER       
     
    350349c$OMP MASTER
    351350          call VTe(VTHallo)
    352 c$OMP END MASTER       
    353 c$OMP BARRIER
    354         else
    355        
    356           stop 'vlspltgen_p : schema non parallelise'
     351c$OMP END MASTER       
     352c$OMP BARRIER
     353        else
     354       
     355          stop 'vlspltgen_p : schema non parallelise'
    357356     
    358357        endif
     
    369368c$OMP MASTER
    370369      call VTe(VTHallo)
    371 c$OMP END MASTER       
     370c$OMP END MASTER       
    372371
    373372c$OMP BARRIER
     
    375374
    376375        if(iadv(iq) == 0) then
    377          
    378           cycle
    379        
    380         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
     376         
     377          cycle
     378       
     379        else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
    381380c$OMP BARRIER       
    382381
     
    388387c$OMP BARRIER       
    389388        else
    390        
    391           stop 'vlspltgen_p : schema non parallelise'
     389       
     390          stop 'vlspltgen_p : schema non parallelise'
    392391     
    393392        endif
     
    414413
    415414        if(iadv(iq) == 0) then
    416        
    417           cycle
    418        
    419         else if (iadv(iq)==10) then
     415       
     416          cycle
     417       
     418        else if (iadv(iq)==10) then
    420419       
    421420          call vly_p(zq(1,1,iq),pente_max,zm(1,1,iq),mv)
    422421 
    423         else if (iadv(iq)==14) then
     422        else if (iadv(iq)==14) then
    424423     
    425424          call vlyqs_p(zq(1,1,iq),pente_max,zm(1,1,iq),mv,qsat)
    426425 
    427426        else
    428        
    429           stop 'vlspltgen_p : schema non parallelise'
     427       
     428          stop 'vlspltgen_p : schema non parallelise'
    430429     
    431430        endif
     
    436435
    437436        if(iadv(iq) == 0) then
    438          
    439           cycle
    440        
    441         else if (iadv(iq)==10) then
     437         
     438          cycle
     439       
     440        else if (iadv(iq)==10) then
    442441       
    443442          call vlx_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,
    444443     &               ij_begin,ij_end)
    445444 
    446         else if (iadv(iq)==14) then
     445        else if (iadv(iq)==14) then
    447446     
    448447          call vlxqs_p(zq(1,1,iq),pente_max,zm(1,1,iq),mu,qsat,
     
    450449 
    451450        else
    452        
     451       
    453452          stop 'vlspltgen_p : schema non parallelise'
    454453     
     
    469468           DO ij=ijb,ije
    470469c             print *,'zq-->',ij,l,iq,zq(ij,l,iq)
    471 c            print *,'q-->',ij,l,iq,q(ij,l,iq)
    472              q(ij,l,iq)=zq(ij,l,iq)
     470c             print *,'q-->',ij,l,iq,q(ij,l,iq)
     471             q(ij,l,iq)=zq(ij,l,iq)
    473472           ENDDO
    474473        ENDDO
  • LMDZ5/trunk/libf/dyn3dpar/vlspltqs_p.F

    r2597 r2600  
    3232#include "paramet.h"
    3333#include "logic.h"
    34 #include "comvert.h"
    3534
    3635c
     
    237236#include "paramet.h"
    238237#include "logic.h"
    239 #include "comvert.h"
    240238c
    241239c
     
    589587#include "paramet.h"
    590588#include "logic.h"
    591 #include "comvert.h"
    592589#include "comgeom.h"
    593590c
  • LMDZ5/trunk/libf/dyn3dpar/writedynav_p.F

    r2598 r2600  
    4343#include "dimensions.h"
    4444#include "paramet.h"
    45 #include "comvert.h"
    4645#include "comgeom.h"
    4746#include "temps.h"
  • LMDZ5/trunk/libf/dyn3dpar/writehist_p.F

    r2598 r2600  
    4343#include "dimensions.h"
    4444#include "paramet.h"
    45 #include "comvert.h"
    4645#include "comgeom.h"
    4746#include "temps.h"
Note: See TracChangeset for help on using the changeset viewer.