Ignore:
Timestamp:
Apr 30, 2015, 12:33:45 PM (10 years ago)
Author:
milmd
Message:

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

Location:
trunk/LMDZ.COMMON/libf
Files:
8 added
130 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/addfi.F

    r1238 r1422  
    88      USE infotrac, ONLY : nqtot
    99      USE control_mod, ONLY : planet_type
     10      USE comconst_mod, ONLY: kappa
    1011      IMPLICIT NONE
    1112c
     
    4849#include "dimensions.h"
    4950#include "paramet.h"
    50 #include "comconst.h"
    5151#include "comgeom.h"
    52 #include "serre.h"
    5352c
    5453c    Arguments :
  • trunk/LMDZ.COMMON/libf/dyn3d/advect.F

    r1 r1422  
    33!
    44      SUBROUTINE advect(ucov,vcov,teta,w,massebx,masseby,du,dv,dteta)
     5
     6      USE comconst_mod, ONLY: daysec
     7      USE logic_mod, ONLY: conser
     8      USE ener_mod, ONLY: gtot
    59
    610      IMPLICIT NONE
     
    2630#include "dimensions.h"
    2731#include "paramet.h"
    28 #include "comconst.h"
    29 #include "comvert.h"
    3032#include "comgeom.h"
    31 #include "logic.h"
    32 #include "ener.h"
    3333
    3434c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3d/advtrac.F90

    r1189 r1422  
    1111  USE infotrac, ONLY: nqtot, iadv
    1212  USE control_mod, ONLY: iapp_tracvl, day_step
     13  USE comconst_mod, ONLY: dtvr
    1314
    1415
     
    1718  include "dimensions.h"
    1819  include "paramet.h"
    19   include "comconst.h"
    20   include "comvert.h"
    2120  include "comdissip.h"
    2221  include "comgeom2.h"
    23   include "logic.h"
    24   include "temps.h"
    25   include "ener.h"
    26   include "description.h"
    2722  include "iniprint.h"
    2823
  • trunk/LMDZ.COMMON/libf/dyn3d/bilan_dyn.F

    r1017 r1422  
    2121      USE control_mod, ONLY: planet_type
    2222      USE cpdet_mod, only: tpot2t
     23      USE comvert_mod, ONLY: ap,bp,presnivs
     24      USE comconst_mod, ONLY: rad,omeg,pi
     25      USE temps_mod, ONLY: annee_ref,day_ref
    2326
    2427      IMPLICIT NONE
     
    2629#include "dimensions.h"
    2730#include "paramet.h"
    28 #include "comconst.h"
    29 #include "comvert.h"
    3031#include "comgeom2.h"
    31 #include "temps.h"
    3232#include "iniprint.h"
    3333
  • trunk/LMDZ.COMMON/libf/dyn3d/caladvtrac.F

    r66 r1422  
    1010      USE infotrac, ONLY : nqtot
    1111      USE control_mod, ONLY : iapp_tracvl,planet_type
     12      USE comconst_mod, ONLY: dtvr
    1213 
    1314      IMPLICIT NONE
     
    2526#include "dimensions.h"
    2627#include "paramet.h"
    27 #include "comconst.h"
    2828
    2929c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3d/caldyn.F

    r1189 r1422  
    55     $ (itau,ucov,vcov,teta,ps,masse,pk,pkf,tsurpk,phis ,
    66     $  phi,conser,du,dv,dteta,dp,w,pbaru,pbarv,time )
     7
     8      USE comvert_mod, ONLY: ap,bp
    79
    810      IMPLICIT NONE
     
    2628#include "dimensions.h"
    2729#include "paramet.h"
    28 #include "comconst.h"
    29 #include "comvert.h"
    3030#include "comgeom.h"
    3131
  • trunk/LMDZ.COMMON/libf/dyn3d/ce0l.F90

    r1302 r1422  
    3939!#include "indicesol.h"
    4040#include "iniprint.h"
    41 #include "temps.h"
    42 #include "logic.h"
    4341  INTEGER, PARAMETER            :: longcles=20
    4442  REAL,    DIMENSION(longcles)  :: clesphy0
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F90

    r1391 r1422  
    1414  use assert_m, only: assert
    1515  use sponge_mod, only: callsponge,mode_sponge,nsponge,tetasponge
     16  USE comconst_mod, ONLY: dissip_factz,dissip_deltaz,dissip_zref,               &
     17                dissip_fac_mid,dissip_fac_up,dissip_hdelta,dissip_pupstart,     &
     18                mode_top_bound,tau_top_bound,iflag_top_bound
     19  USE logic_mod, ONLY: tidal,purmats,ok_guide,read_start,iflag_phys,            &
     20                iflag_trac,ok_strato,ok_gradsfile,ok_limit,ok_etat0,            &
     21                moyzon_mu,moyzon_ch,ok_strato,fxyhypb,ysinus
     22  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,             &
     23                alphax,alphay,taux,tauy
     24  USE temps_mod, ONLY: calend
    1625
    1726  IMPLICIT NONE
     
    3241  include "dimensions.h"
    3342  include "paramet.h"
    34   include "logic.h"
    35   include "serre.h"
    3643  include "comdissnew.h"
    3744  include "iniprint.h"
    38   include "temps.h"
    39   include "comconst.h"
    4045
    4146! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
  • trunk/LMDZ.COMMON/libf/dyn3d/dissip.F

    r1189 r1422  
    44      SUBROUTINE dissip( vcov,ucov,teta,p, dv,du,dh )
    55c
     6      USE comconst_mod, ONLY: dtvr,dtdiss
     7
    68      IMPLICIT NONE
    79
     
    2729#include "dimensions.h"
    2830#include "paramet.h"
    29 #include "comconst.h"
    3031#include "comgeom.h"
    3132#include "comdissnew.h"
  • trunk/LMDZ.COMMON/libf/dyn3d/dteta1.F

    r1 r1422  
    2323#include "dimensions.h"
    2424#include "paramet.h"
    25 #include "logic.h"
    2625
    2726      REAL teta( ip1jmp1,llm ),pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm)
  • trunk/LMDZ.COMMON/libf/dyn3d/dudv2.F

    r1 r1422  
    2828#include "dimensions.h"
    2929#include "paramet.h"
    30 #include "comvert.h"
    3130
    3231      REAL teta( ip1jmp1,llm ),pkf( ip1jmp1,llm ) ,bern( ip1jmp1,llm ),
  • trunk/LMDZ.COMMON/libf/dyn3d/fluxstokenc.F

    r1 r1422  
    1818#include "dimensions.h"
    1919#include "paramet.h"
    20 #include "comconst.h"
    21 #include "comvert.h"
    2220#include "comgeom.h"
    2321#include "tracstoke.h"
    24 #include "temps.h"
    2522#include "iniprint.h"
    2623
  • trunk/LMDZ.COMMON/libf/dyn3d/friction.F

    r1 r1422  
    1212      USE ioipsl_getincom
    1313#endif
     14      USE comconst_mod, ONLY: pi
    1415     
    1516      IMPLICIT NONE
     
    3031#include "paramet.h"
    3132#include "comgeom2.h"
    32 #include "comconst.h"
    3333#include "iniprint.h"
    3434#include "academic.h"
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F

    r1395 r1422  
    2626     &                       less1day,fractday,ndynstep,nsplit_phys
    2727      use cpdet_mod, only: ini_cpdet
     28      USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref,
     29     .          itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end
    2830
    2931#ifdef INCA
     
    4446      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    4547#endif
     48      USE comconst_mod, ONLY: daysec,dtvr,dtphys,rad,g,r,cpp
     49      USE logic_mod, ONLY: read_start,iflag_phys,ok_guide,ecripar
     50
    4651!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    4752
     
    8085#include "dimensions.h"
    8186#include "paramet.h"
    82 #include "comconst.h"
    8387#include "comdissnew.h"
    84 #include "comvert.h"
    8588#include "comgeom.h"
    86 #include "logic.h"
    87 #include "temps.h"
    8889!!!!!!!!!!!#include "control.h"
    89 #include "ener.h"
    90 #include "description.h"
    91 #include "serre.h"
    9290!#include "com_io_dyn.h"
    9391#include "iniprint.h"
     
    166164      abort_message = 'last timestep reached'
    167165      modname = 'gcm'
    168       descript = 'Run GCM LMDZ'
    169166      lafin    = .FALSE.
    170167      dynhist_file = 'dyn_hist.nc'
  • trunk/LMDZ.COMMON/libf/dyn3d/groupe.F

    r841 r1422  
    1818#include "dimensions.h"
    1919#include "paramet.h"
    20 #include "comconst.h"
    2120#include "comgeom2.h"
    22 #include "comvert.h"
    2321
    2422      integer ngroup
  • trunk/LMDZ.COMMON/libf/dyn3d/groupeun.F

    r1 r1422  
    77#include "dimensions.h"
    88#include "paramet.h"
    9 #include "comconst.h"
    109#include "comgeom2.h"
    1110
     
    139138#include "dimensions.h"
    140139#include "paramet.h"
    141 #include "comconst.h"
    142140#include "comgeom2.h"
    143141
  • trunk/LMDZ.COMMON/libf/dyn3d/guide_mod.F90

    r1391 r1422  
    1313  use netcdf, only: nf90_nowrite, nf90_open, nf90_inq_varid, nf90_close
    1414  use pres2lev_mod
     15  USE serre_mod, ONLY: grossismx
    1516
    1617  IMPLICIT NONE
     
    7071    INCLUDE "paramet.h"
    7172    INCLUDE "netcdf.inc"
    72 
    73     ! For grossismx:
    74     include "serre.h"
    7573
    7674    INTEGER                :: error,ncidpl,rid,rcod
     
    313311
    314312    USE control_mod
     313    USE comvert_mod, ONLY: ap,bp,preff,presnivs
     314    USE comconst_mod, ONLY: daysec,dtvr
    315315 
    316316    IMPLICIT NONE
     
    318318    INCLUDE "dimensions.h"
    319319    INCLUDE "paramet.h"
    320     INCLUDE "comconst.h"
    321     INCLUDE "comvert.h"
    322320
    323321    ! Variables entree
     
    540538  SUBROUTINE guide_zonave(typ,hsize,vsize,field)
    541539
     540    USE comconst_mod, ONLY: pi
     541
    542542    IMPLICIT NONE
    543543
     
    545545    INCLUDE "paramet.h"
    546546    INCLUDE "comgeom.h"
    547     INCLUDE "comconst.h"
    548547   
    549548    ! input/output variables
     
    605604  use exner_hyb_m, only: exner_hyb
    606605  use exner_milieu_m, only: exner_milieu
     606  USE comvert_mod, ONLY: ap,bp,preff,pressure_exner
     607  USE comconst_mod, ONLY: cpp,kappa
     608
    607609  IMPLICIT NONE
    608610
    609611  include "dimensions.h"
    610612  include "paramet.h"
    611   include "comvert.h"
    612613  include "comgeom2.h"
    613   include "comconst.h"
    614614
    615615  REAL, DIMENSION (iip1,jjp1),     INTENT(IN) :: psi ! Psol gcm
     
    853853! Calcul des constantes de rappel alpha (=1/tau)
    854854
     855    USE comconst_mod, ONLY: pi
     856    USE serre_mod, ONLY: clon,clat,grossismy
     857
    855858    implicit none
    856859
    857860    include "dimensions.h"
    858861    include "paramet.h"
    859     include "comconst.h"
    860862    include "comgeom2.h"
    861     include "serre.h"
    862863
    863864! input arguments :
     
    15141515  SUBROUTINE guide_out(varname,hsize,vsize,field)
    15151516
     1517    USE comvert_mod, ONLY: presnivs
     1518    USE comconst_mod, ONLY: pi
     1519
    15161520    IMPLICIT NONE
    15171521
     
    15201524    INCLUDE "netcdf.inc"
    15211525    INCLUDE "comgeom2.h"
    1522     INCLUDE "comconst.h"
    1523     INCLUDE "comvert.h"
    15241526   
    15251527    ! Variables entree
  • trunk/LMDZ.COMMON/libf/dyn3d/integrd.F

    r1391 r1422  
    88
    99      use control_mod, only : planet_type
     10      USE comvert_mod, ONLY: ap,bp
     11      USE comconst_mod, ONLY: pi
     12      USE logic_mod, ONLY: leapf
     13      USE temps_mod, ONLY: dt
    1014
    1115      IMPLICIT NONE
     
    2933#include "dimensions.h"
    3034#include "paramet.h"
    31 #include "comconst.h"
    3235#include "comgeom.h"
    33 #include "comvert.h"
    34 #include "logic.h"
    35 #include "temps.h"
    36 #include "serre.h"
    3736#include "iniprint.h"
    3837
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r1414 r1422  
    2525      use sponge_mod, only: callsponge,mode_sponge,sponge
    2626       use comuforc_h
     27      USE comvert_mod, ONLY: ap,bp,pressure_exner,presnivs
     28      USE comconst_mod, ONLY: daysec,dtvr,dtphys,dtdiss,
     29     .                  cpp,ihf,iflag_top_bound,pi
     30      USE logic_mod, ONLY: iflag_phys,ok_guide,forward,leapf,apphys,
     31     .                  statcl,conser,apdiss,purmats,tidal,ok_strato
     32      USE temps_mod, ONLY: jD_ref,jH_ref,itaufin,day_ini,day_ref,
     33     .                  start_time,dt
    2734
    2835      IMPLICIT NONE
     
    6168#include "dimensions.h"
    6269#include "paramet.h"
    63 #include "comconst.h"
    6470#include "comdissnew.h"
    65 #include "comvert.h"
    6671#include "comgeom.h"
    67 #include "logic.h"
    68 #include "temps.h"
    69 #include "ener.h"
    70 #include "description.h"
    71 #include "serre.h"
    7272!#include "com_io_dyn.h"
    7373#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/dyn3d/qminimum.F

    r1 r1422  
    1111#include "dimensions.h"
    1212#include "paramet.h"
    13 #include "comvert.h"
    1413c
    1514      INTEGER nq
  • trunk/LMDZ.COMMON/libf/dyn3d/sponge_mod.F90

    r1017 r1422  
    2929! A(t+dt)=A(t)-(A(t)-Am)*(1-exp(-lambda*dt))
    3030
     31      USE comvert_mod, ONLY: ap,bp,preff,scaleheight
    3132
    3233      implicit none
     
    3435#include "paramet.h"
    3536#include "comdissip.h"
    36 #include "comvert.h"
    3737#include "comgeom2.h"
    3838#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/dyn3d/sw_case_williamson91_6.F

    r1 r1422  
    2626c
    2727c=======================================================================
     28      USE comvert_mod, ONLY: ap,bp,preff
     29      USE comconst_mod, ONLY: cpp,omeg,rad
     30
    2831      IMPLICIT NONE
    2932c-----------------------------------------------------------------------
     
    3336#include "dimensions.h"
    3437#include "paramet.h"
    35 #include "comvert.h"
    36 #include "comconst.h"
    3738#include "comgeom.h"
    3839#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/dyn3d/top_bound.F

    r1012 r1422  
    33!
    44      SUBROUTINE top_bound(vcov,ucov,teta,masse,dt,ducov)
     5
     6      USE comvert_mod, ONLY: presnivs,scaleheight,preff
     7      USE comconst_mod, ONLY: iflag_top_bound,tau_top_bound,
     8     .                  mode_top_bound
     9
    510      IMPLICIT NONE
    611c
    712#include "dimensions.h"
    813#include "paramet.h"
    9 #include "comconst.h"
    10 #include "comvert.h"
    1114#include "comgeom2.h"
    1215
  • trunk/LMDZ.COMMON/libf/dyn3d/vlsplt.F

    r270 r1422  
    2222#include "dimensions.h"
    2323#include "paramet.h"
    24 #include "logic.h"
    25 #include "comvert.h"
    26 #include "comconst.h"
    2724
    2825c
     
    131128      include "dimensions.h"
    132129      include "paramet.h"
    133       include "logic.h"
    134       include "comvert.h"
    135       include "comconst.h"
    136130      include "iniprint.h"
    137131c
     
    452446c
    453447c   --------------------------------------------------------------------
     448      USE comconst_mod, ONLY: pi
     449
    454450      IMPLICIT NONE
    455451c
    456452#include "dimensions.h"
    457453#include "paramet.h"
    458 #include "logic.h"
    459 #include "comvert.h"
    460 #include "comconst.h"
    461454#include "comgeom.h"
    462455c
     
    772765#include "dimensions.h"
    773766#include "paramet.h"
    774 #include "logic.h"
    775 #include "comvert.h"
    776 #include "comconst.h"
    777767c
    778768c
  • trunk/LMDZ.COMMON/libf/dyn3d/vlspltqs.F

    r1017 r1422  
    2727#include "dimensions.h"
    2828#include "paramet.h"
    29 #include "logic.h"
    30 #include "comvert.h"
    31 #include "comconst.h"
    3229
    3330c
     
    174171#include "dimensions.h"
    175172#include "paramet.h"
    176 #include "logic.h"
    177 #include "comvert.h"
    178 #include "comconst.h"
    179173c
    180174c
     
    492486c
    493487c   --------------------------------------------------------------------
     488      USE comconst_mod, ONLY: pi
     489
    494490      IMPLICIT NONE
    495491c
    496492#include "dimensions.h"
    497493#include "paramet.h"
    498 #include "logic.h"
    499 #include "comvert.h"
    500 #include "comconst.h"
    501494#include "comgeom.h"
    502495c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/adaptdt.F

    r1300 r1422  
    66
    77      USE control_mod
     8      USE comconst_mod, ONLY: dtvr
    89      IMPLICIT NONE
    910
     
    1112c#include "paramr2.h"
    1213#include "paramet.h"
    13 #include "comconst.h"
    1414#include "comdissip.h"
    15 #include "comvert.h"
    1615#include "comgeom2.h"
    17 #include "logic.h"
    18 #include "temps.h"
    19 #include "ener.h"
    20 #include "description.h"
    2116
    2217c----------------------------------------------------------
  • trunk/LMDZ.COMMON/libf/dyn3d_common/advn.F

    r1300 r1422  
    1919#include "dimensions.h"
    2020#include "paramet.h"
    21 #include "logic.h"
    22 #include "comvert.h"
    23 #include "comconst.h"
    2421#include "comgeom.h"
    2522#include "iniprint.h"
     
    486483#include "dimensions.h"
    487484#include "paramet.h"
    488 #include "logic.h"
    489 #include "comvert.h"
    490 #include "comconst.h"
    491485#include "iniprint.h"
    492486c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/advx.F

    r1300 r1422  
    2525#include "dimensions.h"
    2626#include "paramet.h"
    27 #include "comconst.h"
    28 #include "comvert.h"
    2927
    3028C  Arguments :
  • trunk/LMDZ.COMMON/libf/dyn3d_common/advxp.F

    r1300 r1422  
    1515#include "dimensions.h"
    1616#include "paramet.h"
    17 #include "comconst.h"
    18 #include "comvert.h"
    1917
    2018       INTEGER ntra
  • trunk/LMDZ.COMMON/libf/dyn3d_common/advy.F

    r1300 r1422  
    2828#include "dimensions.h"
    2929#include "paramet.h"
    30 #include "comconst.h"
    31 #include "comvert.h"
    3230#include "comgeom2.h"
    3331 
  • trunk/LMDZ.COMMON/libf/dyn3d_common/advyp.F

    r1300 r1422  
    3030#include "dimensions.h"
    3131#include "paramet.h"
    32 #include "comconst.h"
    33 #include "comvert.h"
    3432#include "comgeom.h"
    3533 
  • trunk/LMDZ.COMMON/libf/dyn3d_common/advz.F

    r1300 r1422  
    2323#include "dimensions.h"
    2424#include "paramet.h"
    25 #include "comconst.h"
    26 #include "comvert.h"
    2725
    2826C    #include "traceur.h"
  • trunk/LMDZ.COMMON/libf/dyn3d_common/advzp.F

    r1300 r1422  
    3333#include "dimensions.h"
    3434#include "paramet.h"
    35 #include "comconst.h"
    36 #include "comvert.h"
    3735#include "comgeom.h"
    3836C
  • trunk/LMDZ.COMMON/libf/dyn3d_common/bernoui.F

    r1300 r1422  
    2727#include "dimensions.h"
    2828#include "paramet.h"
    29 #include "logic.h"
    3029c
    3130c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3d_common/conf_planete.F90

    r1300 r1422  
    1010USE ioipsl_getincom
    1111#endif
     12USE comvert_mod, ONLY: preff,pa
     13USE comconst_mod, ONLY: daysec,daylen,kappa,cpp,omeg,rad,g,ihf,pi,molmass
    1214IMPLICIT NONE
    1315!
     
    1618!   --------------
    1719#include "dimensions.h"
    18 #include "comconst.h"
    19 #include "comvert.h"
    2020!
    2121!   local:
  • trunk/LMDZ.COMMON/libf/dyn3d_common/convmas.F

    r1300 r1422  
    3434#include "dimensions.h"
    3535#include "paramet.h"
    36 #include "comvert.h"
    37 #include "logic.h"
    3836
    3937      REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm ),convm(  ip1jmp1,llm )
  • trunk/LMDZ.COMMON/libf/dyn3d_common/coordij.F

    r1300 r1422  
    1010c
    1111c=======================================================================
     12      USE comconst_mod, ONLY: pi
    1213
    1314      IMPLICIT NONE
     
    1819#include "dimensions.h"
    1920#include "paramet.h"
    20 #include "comconst.h"
    2121#include "comgeom.h"
    22 #include "serre.h"
    2322
    2423      real zlon,zlat
  • trunk/LMDZ.COMMON/libf/dyn3d_common/cpdet_mod.F90

    r1315 r1422  
    2222     
    2323      USE control_mod, ONLY: planet_type
     24      USE comconst_mod, ONLY: nu_venus,t0_venus
    2425      IMPLICIT none
    2526!======================================================================
    2627! Initialization of nu_venus and t0_venus
    2728!======================================================================
    28 
    29 ! for cpp, nu_venus and t0_venus:
    30 #include "comconst.h"
    3129
    3230      if (planet_type.eq."venus") then
     
    4745
    4846      USE control_mod, ONLY: planet_type
     47      USE comconst_mod, ONLY: cpp,t0_venus,nu_venus
    4948      IMPLICIT none
    5049
    5150! for cpp, nu_venus and t0_venus:
    52 #include "comconst.h"
    5351
    5452      real,intent(in) :: t
     
    7876
    7977      USE control_mod, ONLY: planet_type
     78      USE comconst_mod, ONLY: cpp,t0_venus,nu_venus
     79
    8080      IMPLICIT NONE
    81      
    82 ! for cpp, nu_venus and t0_venus:
    83 #include "comconst.h"
    8481
    8582      integer,intent(in) :: npoints
     
    112109
    113110      USE control_mod, ONLY: planet_type
     111      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
     112
    114113      IMPLICIT NONE
    115 
    116 ! for cpp, nu_venus and t0_venus:
    117 #include "comconst.h"
    118114
    119115      integer,intent(in) :: npoints
     
    143139      USE control_mod, only : planet_type
    144140      USE parallel_lmdz, only : OMP_CHUNK
    145       IMPLICIT none
    146 
    147 ! for cpp, nu_venus and t0_venus:
    148 #include "comconst.h"
     141      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
     142
     143      IMPLICIT none
    149144
    150145      integer,intent(in) :: nlon,nlev
     
    182177      USE parallel_lmdz, only : jj_begin,jj_end,OMP_CHUNK
    183178      USE control_mod, only : planet_type
     179      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
     180
    184181      IMPLICIT none
    185182! for iip1, jjp1 and llm
    186183#include "dimensions.h"
    187184#include "paramet.h"
    188 ! for cpp, nu_venus and t0_venus:
    189 #include "comconst.h"
    190185
    191186      real,intent(in) :: yt(iip1,jjp1,llm)
     
    225220      USE control_mod, only : planet_type
    226221      USE parallel_lmdz, only : OMP_CHUNK
    227       IMPLICIT none
    228 ! for cpp, nu_venus and t0_venus:
    229 #include "comconst.h"
     222      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
     223
     224      IMPLICIT none
    230225
    231226      integer,intent(in) :: nlon,nlev
     
    263258      USE parallel_lmdz, only : jj_begin,jj_end,OMP_CHUNK
    264259      USE control_mod, only : planet_type
     260      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
     261
    265262      IMPLICIT none
    266263! for iip1, jjp1 and llm
    267264#include "dimensions.h"
    268265#include "paramet.h"
    269 ! for cpp, nu_venus and t0_venus:
    270 #include "comconst.h"
    271266
    272267      real,intent(out) :: yt(iip1,jjp1,llm)
  • trunk/LMDZ.COMMON/libf/dyn3d_common/defrun.F

    r1300 r1422  
    1313
    1414      USE control_mod
     15      USE logic_mod, ONLY: purmats,iflag_phys,fxyhypb,ysinus
     16      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
     17     .          alphax,alphay,taux,tauy
    1518 
    1619      IMPLICIT NONE
     
    3639#include "dimensions.h"
    3740#include "paramet.h"
    38 #include "logic.h"
    39 #include "serre.h"
    4041#include "comdissnew.h"
    4142#include "clesph0.h"
  • trunk/LMDZ.COMMON/libf/dyn3d_common/disvert.F90

    r1391 r1422  
    1212  use new_unit_m, only: new_unit
    1313  use assert_m, only: assert
     14  USE comvert_mod, ONLY: ap,bp,nivsigs,nivsig,preff,pa,presnivs,dpres,scaleheight
     15  USE logic_mod, ONLY: ok_strato
    1416
    1517  IMPLICIT NONE
     
    1719  include "dimensions.h"
    1820  include "paramet.h"
    19   include "comvert.h"
    20   include "comconst.h"
    2121  include "iniprint.h"
    22   include "logic.h"
    2322
    2423!-------------------------------------------------------------------------------
  • trunk/LMDZ.COMMON/libf/dyn3d_common/disvert_noterre.F

    r1300 r1422  
    1212      use ioipsl_getincom
    1313#endif
     14      USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,
     15     .                  nivsig,nivsigs,pa,preff,scaleheight
     16      USE comconst_mod, ONLY: kappa
     17      USE logic_mod, ONLY: hybrid
    1418
    1519      IMPLICIT NONE
     
    1721#include "dimensions.h"
    1822#include "paramet.h"
    19 #include "comvert.h"
    20 #include "comconst.h"
    21 #include "logic.h"
    2223#include "iniprint.h"
    2324c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/divgrad.F

    r1300 r1422  
    2424#include "comgeom.h"
    2525#include "comdissipn.h"
    26 #include "logic.h"
    2726c
    2827      INTEGER klevel
  • trunk/LMDZ.COMMON/libf/dyn3d_common/dynetat0.F

    r1300 r1422  
    1111
    1212      use control_mod, only : planet_type, timestart
     13      USE comvert_mod, ONLY: pa,preff
     14      USE comconst_mod, ONLY: im,jm,lllm,daysec,dtvr,
     15     .                  rad,omeg,g,cpp,kappa,pi
     16      USE logic_mod, ONLY: fxyhypb,ysinus
     17      USE serre_mod, ONLY: clon,clat,grossismx,grossismy
     18      USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn,
     19     .                  start_time,day_ini,hour_ini
     20      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1321
    1422      IMPLICIT NONE
     
    3139#include "dimensions.h"
    3240#include "paramet.h"
    33 #include "temps.h"
    34 #include "comconst.h"
    35 #include "comvert.h"
    3641#include "comgeom2.h"
    37 #include "ener.h"
    3842#include "netcdf.inc"
    39 #include "description.h"
    40 #include "serre.h"
    41 #include "logic.h"
    4243#include "iniprint.h"
    4344
  • trunk/LMDZ.COMMON/libf/dyn3d_common/dynredem.F

    r1300 r1422  
    1010      use netcdf95, only: NF95_PUT_VAR
    1111      use control_mod, only : planet_type
     12      USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,pa,preff,
     13     .                  nivsig,nivsigs
     14      USE comconst_mod, ONLY: daysec,dtvr,rad,omeg,g,cpp,kappa,pi
     15      USE logic_mod, ONLY: fxyhypb,ysinus
     16      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
     17     .                  taux,tauy
     18      USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn,itaufin,
     19     .                  start_time,hour_ini
     20      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1221
    1322      IMPLICIT NONE
     
    1928#include "dimensions.h"
    2029#include "paramet.h"
    21 #include "comconst.h"
    22 #include "comvert.h"
    2330#include "comgeom2.h"
    24 #include "temps.h"
    25 #include "ener.h"
    26 #include "logic.h"
    2731#include "netcdf.inc"
    28 #include "description.h"
    29 #include "serre.h"
    3032#include "iniprint.h"
    3133
     
    588590      use netcdf, only: NF90_get_VAR
    589591      use netcdf95, only: NF95_PUT_VAR
     592      USE temps_mod, ONLY: itaufin,itau_dyn
    590593 
    591594      IMPLICIT NONE
     
    595598#include "dimensions.h"
    596599#include "paramet.h"
    597 #include "description.h"
    598600#include "netcdf.inc"
    599 #include "comvert.h"
    600601#include "comgeom.h"
    601 #include "temps.h"
    602602#include "iniprint.h"
    603603
  • trunk/LMDZ.COMMON/libf/dyn3d_common/exner_hyb_m.F90

    r1302 r1422  
    11module exner_hyb_m
     2
     3  USE comvert_mod, ONLY: preff
     4  USE comconst_mod, ONLY: jmp1,kappa,cpp,r,pi
    25
    36  IMPLICIT NONE
     
    3538    include "dimensions.h"
    3639    include "paramet.h"
    37     include "comconst.h"
    3840    include "comgeom.h"
    39     include "comvert.h"
    40     include "serre.h"
    4141
    4242    INTEGER  ngrid
  • trunk/LMDZ.COMMON/libf/dyn3d_common/exner_milieu_m.F90

    r1302 r1422  
    11module exner_milieu_m
     2
     3  USE comvert_mod, ONLY: preff
     4  USE comconst_mod, ONLY: jmp1,kappa,cpp,r
    25
    36  IMPLICIT NONE
     
    3235    include "dimensions.h"
    3336    include "paramet.h"
    34     include "comconst.h"
    3537    include "comgeom.h"
    36     include "comvert.h"
    37     include "serre.h"
    3838
    3939    INTEGER  ngrid
  • trunk/LMDZ.COMMON/libf/dyn3d_common/fxy.F

    r1300 r1422  
    55     ,                    rlatu2,yprimu2,
    66     , rlonu,xprimu,rlonv,xprimv,rlonm025,xprimm025,rlonp025,xprimp025)
     7
     8      USE comconst_mod, ONLY: pi
     9      USE serre_mod, ONLY: pxo,pyo,alphax,alphay,transx,transy
    710
    811      IMPLICIT NONE
     
    1619#include "dimensions.h"
    1720#include "paramet.h"
    18 #include "serre.h"
    19 #include "comconst.h"
    2021
    2122       INTEGER i,j
  • trunk/LMDZ.COMMON/libf/dyn3d_common/fxysinus.F

    r1300 r1422  
    66     ,  rlonu,xprimu,rlonv,xprimv,rlonm025,xprimm025,rlonp025,xprimp025)
    77
     8      USE comconst_mod, ONLY: pi
    89
    910      IMPLICIT NONE
     
    1718#include "dimensions.h"
    1819#include "paramet.h"
    19 #include "comconst.h"
    2020
    2121       INTEGER i,j
  • trunk/LMDZ.COMMON/libf/dyn3d_common/geopot.F

    r1300 r1422  
    2929#include "dimensions.h"
    3030#include "paramet.h"
    31 #include "comvert.h"
    3231
    3332c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3d_common/gradiv.F

    r1300 r1422  
    2222#include "paramet.h"
    2323#include "comdissipn.h"
    24 #include "logic.h"
    2524
    2625      INTEGER klevel
  • trunk/LMDZ.COMMON/libf/dyn3d_common/grilles_gcm_netcdf_sub.F90

    r1300 r1422  
    99SUBROUTINE grilles_gcm_netcdf_sub(masque,phis)
    1010
     11  USE comvert_mod, ONLY: pa,preff,presnivs
     12  USE comconst_mod, ONLY: daysec,rad,omeg,g,kappa,cpp,pi
     13
    1114  IMPLICIT NONE
    1215
    1316  INCLUDE "dimensions.h"
    1417  INCLUDE "paramet.h"
    15   INCLUDE "comconst.h"
    1618  INCLUDE "comgeom.h"
    17   INCLUDE "comvert.h"
    1819  INCLUDE "netcdf.inc"
    19   INCLUDE "serre.h"
    2020
    2121
  • trunk/LMDZ.COMMON/libf/dyn3d_common/iniacademic.F90

    r1391 r1422  
    1616  use exner_hyb_m, only: exner_hyb
    1717  use exner_milieu_m, only: exner_milieu
     18  USE comvert_mod, ONLY: ap,bp,preff,presnivs,pressure_exner
     19  USE comconst_mod, ONLY: im,jm,daysec,dtvr,kappa,cpp,g,pi
     20  USE logic_mod, ONLY: iflag_phys,read_start
     21  USE temps_mod, ONLY: annee_ref,day_ref,day_ini
     22  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1823
    1924  !   Author:    Frederic Hourdin      original: 15/01/93
     
    2833  include "dimensions.h"
    2934  include "paramet.h"
    30   include "comvert.h"
    31   include "comconst.h"
    3235  include "comgeom.h"
    3336  include "academic.h"
    34   include "ener.h"
    35   include "temps.h"
    3637  include "iniprint.h"
    37   include "logic.h"
    3838
    3939  !   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3d_common/iniconst.F90

    r1302 r1422  
    1111  use ioipsl_getincom
    1212#endif
     13  USE comvert_mod, ONLY: disvert_type,pressure_exner
     14  USE comconst_mod, ONLY: im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,   &
     15                dtphys,dtvr,unsim,r,cpp,kappa,pi
    1316
    1417  IMPLICIT NONE
     
    2124  include "dimensions.h"
    2225  include "paramet.h"
    23   include "comconst.h"
    24   include "temps.h"
    25   include "comvert.h"
    2626  include "iniprint.h"
    2727
  • trunk/LMDZ.COMMON/libf/dyn3d_common/inidissip.F90

    r1300 r1422  
    2525
    2626  USE control_mod, only : dissip_period,iperiod,planet_type
     27  USE comvert_mod, ONLY: preff,presnivs,scaleheight,pseudoalt
     28  USE comconst_mod, ONLY: dtvr,dtdiss,rad,pi,dissip_zref,dissip_deltaz,         &
     29                dissip_factz,dissip_fac_mid,dissip_fac_up,dissip_pupstart,      &
     30                dissip_hdelta   
     31  USE logic_mod, ONLY: ok_strato
    2732
    2833  IMPLICIT NONE
     
    3035  include "paramet.h"
    3136  include "comdissipn.h"
    32   include "comconst.h"
    33   include "comvert.h"
    34   include "logic.h"
    3537  include "iniprint.h"
    3638
  • trunk/LMDZ.COMMON/libf/dyn3d_common/inigeom.F

    r1300 r1422  
    1616c
    1717c
     18      USE comconst_mod, ONLY: rad,g,omeg,pi
     19      USE logic_mod, ONLY: fxyhypb,ysinus
     20      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
     21     .          alphax,alphay,taux,tauy,transx,transy,pxo,pyo
     22
    1823      IMPLICIT NONE
    1924c
    2025#include "dimensions.h"
    2126#include "paramet.h"
    22 #include "comconst.h"
    2327#include "comgeom2.h"
    24 #include "serre.h"
    25 #include "logic.h"
    2628#include "comdissnew.h"
    2729
  • trunk/LMDZ.COMMON/libf/dyn3d_common/initdynav.F90

    r1403 r1422  
    99  use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid, &
    1010       dynhistave_file,dynhistvave_file,dynhistuave_file
     11  USE comvert_mod, ONLY: presnivs
     12  USE comconst_mod, ONLY: pi
     13  USE temps_mod, ONLY: itau_dyn
    1114  implicit none
    1215
     
    3437  include "dimensions.h"
    3538  include "paramet.h"
    36   include "comconst.h"
    37   include "comvert.h"
    3839  include "comgeom.h"
    39   include "temps.h"
    40   include "ener.h"
    41   include "logic.h"
    42   include "description.h"
    43   include "serre.h"
    4440  include "iniprint.h"
    4541
  • trunk/LMDZ.COMMON/libf/dyn3d_common/initfluxsto.F

    r1403 r1422  
    99       USE IOIPSL
    1010#endif
     11       USE comvert_mod, ONLY: nivsigs
     12       USE comconst_mod, ONLY: pi
     13       USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn
    1114      implicit none
    1215
     
    4043#include "dimensions.h"
    4144#include "paramet.h"
    42 #include "comconst.h"
    43 #include "comvert.h"
    4445#include "comgeom.h"
    45 #include "temps.h"
    46 #include "ener.h"
    47 #include "logic.h"
    48 #include "description.h"
    49 #include "serre.h"
    5046#include "iniprint.h"
    5147
  • trunk/LMDZ.COMMON/libf/dyn3d_common/inithist.F

    r1403 r1422  
    1010       use com_io_dyn_mod, only : histid,histvid,histuid,               &
    1111     &                        dynhist_file,dynhistv_file,dynhistu_file
     12       USE comvert_mod, ONLY: presnivs
     13       USE comconst_mod, ONLY: pi
     14       USE temps_mod, ONLY: itau_dyn
    1215
    1316      implicit none
     
    4043#include "dimensions.h"
    4144#include "paramet.h"
    42 #include "comconst.h"
    43 #include "comvert.h"
    4445#include "comgeom.h"
    45 #include "temps.h"
    46 #include "ener.h"
    47 #include "logic.h"
    48 #include "description.h"
    49 #include "serre.h"
    5046#include "iniprint.h"
    5147
  • trunk/LMDZ.COMMON/libf/dyn3d_common/inter_barxy_m.F90

    r1300 r1422  
    374374
    375375    use assert_eq_m, only: assert_eq
     376    USE comconst_mod, ONLY: pi
    376377
    377378    IMPLICIT NONE
    378379
    379     include "comconst.h"
    380380    ! (for "pi")
    381381
     
    431431    ! order.
    432432
     433    USE comconst_mod, ONLY: pi
     434
    433435    IMPLICIT NONE
    434436
    435     include "comconst.h"
    436437    ! (for "pi")
    437438
  • trunk/LMDZ.COMMON/libf/dyn3d_common/interpost.F

    r1300 r1422  
    99#include "dimensions.h"
    1010#include "paramet.h"
    11 #include "comconst.h"
    12 #include "comvert.h"
    1311#include "comgeom2.h"
    1412
  • trunk/LMDZ.COMMON/libf/dyn3d_common/interpre.F

    r1391 r1422  
    77
    88      USE control_mod
     9      USE comvert_mod, ONLY: ap,bp
     10      USE comconst_mod, ONLY: g
    911
    1012       implicit none
     
    1315c#include "paramr2.h"
    1416#include "paramet.h"
    15 #include "comconst.h"
    1617#include "comdissip.h"
    17 #include "comvert.h"
    1818#include "comgeom2.h"
    19 #include "logic.h"
    20 #include "temps.h"
    21 #include "ener.h"
    22 #include "description.h"
    2319
    2420c---------------------------------------------------
  • trunk/LMDZ.COMMON/libf/dyn3d_common/limx.F

    r1300 r1422  
    1717#include "dimensions.h"
    1818#include "paramet.h"
    19 #include "logic.h"
    20 #include "comvert.h"
    21 #include "comconst.h"
    2219#include "comgeom.h"
    2320c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/limy.F

    r1300 r1422  
    1414c
    1515c   --------------------------------------------------------------------
     16      USE comconst_mod, ONLY: pi
     17
    1618      IMPLICIT NONE
    1719c
    1820#include "dimensions.h"
    1921#include "paramet.h"
    20 #include "logic.h"
    21 #include "comvert.h"
    22 #include "comconst.h"
    2322#include "comgeom.h"
    2423c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/limz.F

    r1300 r1422  
    1717#include "dimensions.h"
    1818#include "paramet.h"
    19 #include "logic.h"
    20 #include "comvert.h"
    21 #include "comconst.h"
    2219#include "comgeom.h"
    2320c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/massbar.F

    r1391 r1422  
    2020#include "dimensions.h"
    2121#include "paramet.h"
    22 #include "comconst.h"
    2322#include "comgeom.h"
    2423c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/massbarxy.F

    r1391 r1422  
    2020#include "dimensions.h"
    2121#include "paramet.h"
    22 #include "comconst.h"
    2322#include "comgeom.h"
    2423c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/massdair.F

    r1300 r1422  
    2020#include "dimensions.h"
    2121#include "paramet.h"
    22 #include "comconst.h"
    2322#include "comgeom.h"
    2423c
  • trunk/LMDZ.COMMON/libf/dyn3d_common/nxgrarot.F

    r1300 r1422  
    2222#include "paramet.h"
    2323#include "comdissipn.h"
    24 #include "logic.h"
    2524c
    2625      INTEGER klevel
  • trunk/LMDZ.COMMON/libf/dyn3d_common/pentes_ini.F

    r1300 r1422  
    33!
    44      SUBROUTINE pentes_ini (q,w,masse,pbaru,pbarv,mode)
     5
     6      USE comconst_mod, ONLY: dtvr,pi
     7
    58      IMPLICIT NONE
    69
     
    2427#include "dimensions.h"
    2528#include "paramet.h"
    26 #include "comconst.h"
    27 #include "comvert.h"
    2829#include "comgeom2.h"
    2930
  • trunk/LMDZ.COMMON/libf/dyn3d_common/prather.F

    r1300 r1422  
    33!
    44      SUBROUTINE prather (q,w,masse,pbaru,pbarv,nt,dt)
     5
     6      USE comconst_mod, ONLY: pi
     7
    58      IMPLICIT NONE
    69
     
    2124#include "dimensions.h"
    2225#include "paramet.h"
    23 #include "comconst.h"
    24 #include "comvert.h"
    2526#include "comgeom2.h"
    2627
  • trunk/LMDZ.COMMON/libf/dyn3d_common/sortvarc.F

    r1391 r1422  
    77
    88      USE control_mod, ONLY: resetvarc
     9      USE comconst_mod, ONLY: daysec,dtvr,rad,g,omeg
     10      USE logic_mod, ONLY: read_start
     11      USE ener_mod, ONLY: etot,ptot,ztot,stot,ang,
     12     .                  etot0,ptot0,ztot0,stot0,ang0,
     13     .                  rmsdpdt,rmsv
    914      IMPLICIT NONE
    1015
     
    2732      INCLUDE "dimensions.h"
    2833      INCLUDE "paramet.h"
    29       INCLUDE "comconst.h"
    30       INCLUDE "comvert.h"
    3134      INCLUDE "comgeom.h"
    32       INCLUDE "ener.h"
    33       INCLUDE "logic.h"
    34       INCLUDE "temps.h"
    3535      INCLUDE "iniprint.h"
    3636
  • trunk/LMDZ.COMMON/libf/dyn3d_common/sortvarc0.F

    r1300 r1422  
    55     $(itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time ,
    66     $ vcov)
     7
     8      USE comconst_mod, ONLY: daysec,dtvr,rad,g,omeg
     9      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0,rmsv,rmsdpdt
     10
    711      IMPLICIT NONE
    812
     
    2428#include "dimensions.h"
    2529#include "paramet.h"
    26 #include "comconst.h"
    27 #include "comvert.h"
    2830#include "comgeom.h"
    29 #include "ener.h"
    30 #include "logic.h"
    31 #include "temps.h"
    3231
    3332c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3d_common/tidal_forces.F

    r1300 r1422  
    2424#include "dimensions.h"
    2525#include "paramet.h"
    26 #include "logic.h"
    27 #include "comvert.h"
    28 #include "comconst.h"
    2926#include "comgeom.h"
    3027!#include "comorbit.h"
  • trunk/LMDZ.COMMON/libf/dyn3d_common/tourpot.F

    r1300 r1422  
    2525#include "paramet.h"
    2626#include "comgeom.h"
    27 #include "logic.h"
    2827
    2928      REAL  rot( ip1jm,llm )
  • trunk/LMDZ.COMMON/libf/dyn3d_common/traceurpole.F

    r1300 r1422  
    1111c#include "paramr2.h"
    1212#include "paramet.h"
    13 #include "comconst.h"
    1413#include "comdissip.h"
    15 #include "comvert.h"
    1614#include "comgeom2.h"
    17 #include "logic.h"
    18 #include "temps.h"
    19 #include "ener.h"
    20 #include "description.h"
    2115
    2216
  • trunk/LMDZ.COMMON/libf/dyn3d_common/ugeostr.F90

    r1415 r1422  
    1111  ! levels are pressure levels.
    1212
     13  USE comconst_mod, ONLY: omeg,rad
     14
    1315  implicit none
    1416
    1517  include "dimensions.h"
    1618  include "paramet.h"
    17   include "comconst.h"
    1819  include "comgeom2.h"
    1920
  • trunk/LMDZ.COMMON/libf/dyn3d_common/vitvert.F

    r1300 r1422  
    44      SUBROUTINE vitvert ( convm , w )
    55c
     6      USE comvert_mod, ONLY: bp
     7
    68      IMPLICIT NONE
    79
     
    3032#include "dimensions.h"
    3133#include "paramet.h"
    32 #include "comvert.h"
    3334
    3435      REAL w(ip1jmp1,llm),convm(ip1jmp1,llm)
  • trunk/LMDZ.COMMON/libf/dyn3d_common/writedynav.F90

    r1403 r1422  
    88  USE infotrac, ONLY : nqtot, ttext
    99  use com_io_dyn_mod, only : histaveid, histvaveid, histuaveid
     10  USE comconst_mod, ONLY: cpp
     11  USE temps_mod, ONLY: itau_dyn
    1012
    1113  implicit none
     
    3133  include "dimensions.h"
    3234  include "paramet.h"
    33   include "comconst.h"
    34   include "comvert.h"
    3535  include "comgeom.h"
    36   include "temps.h"
    37   include "ener.h"
    38   include "logic.h"
    39   include "description.h"
    40   include "serre.h"
    4136  include "iniprint.h"
    4237
  • trunk/LMDZ.COMMON/libf/dyn3d_common/writehist.F

    r1403 r1422  
    99      USE infotrac, ONLY : nqtot, ttext
    1010      use com_io_dyn_mod, only : histid,histvid,histuid
     11      USE temps_mod, ONLY: itau_dyn
    1112      implicit none
    1213
     
    3536#include "dimensions.h"
    3637#include "paramet.h"
    37 #include "comconst.h"
    38 #include "comvert.h"
    3938#include "comgeom.h"
    40 #include "temps.h"
    41 #include "ener.h"
    42 #include "logic.h"
    43 #include "description.h"
    44 #include "serre.h"
    4539#include "iniprint.h"
    4640
  • trunk/LMDZ.COMMON/libf/dyn3dpar/addfi_p.F

    r1348 r1422  
    88      USE infotrac, ONLY : nqtot
    99      USE control_mod, ONLY : planet_type
     10      USE comconst_mod, ONLY: kappa
    1011      IMPLICIT NONE
    1112c
     
    4849#include "dimensions.h"
    4950#include "paramet.h"
    50 #include "comconst.h"
    5151#include "comgeom.h"
    52 #include "serre.h"
    5352c
    5453c    Arguments :
  • trunk/LMDZ.COMMON/libf/dyn3dpar/advect_new_p.F

    r1019 r1422  
    66      USE parallel_lmdz
    77      USE write_field_p
     8      USE comconst_mod, ONLY: daysec
     9      USE logic_mod, ONLY: conser
    810      IMPLICIT NONE
    911c=======================================================================
     
    2830#include "dimensions.h"
    2931#include "paramet.h"
    30 #include "comconst.h"
    31 #include "comvert.h"
    3232#include "comgeom.h"
    33 #include "logic.h"
    34 #include "ener.h"
    3533
    3634c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3dpar/advect_p.F

    r1019 r1422  
    55      USE parallel_lmdz
    66      USE write_field_p
     7      USE comconst_mod, ONLY: daysec
     8      USE logic_mod, ONLY: conser
    79      IMPLICIT NONE
    810c=======================================================================
     
    2729#include "dimensions.h"
    2830#include "paramet.h"
    29 #include "comconst.h"
    30 #include "comvert.h"
    3131#include "comgeom.h"
    32 #include "logic.h"
    33 #include "ener.h"
    3432
    3533c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3dpar/advtrac_p.F90

    r1189 r1422  
    1818  USE infotrac, ONLY: nqtot, iadv
    1919  USE control_mod, ONLY: iapp_tracvl, day_step, planet_type
     20  USE comconst_mod, ONLY: dtvr
    2021  IMPLICIT NONE
    2122  !
    2223  include "dimensions.h"
    2324  include "paramet.h"
    24   include "comconst.h"
    25   include "comvert.h"
    2625  include "comdissip.h"
    2726  include "comgeom2.h"
    28   include "logic.h"
    29   include "temps.h"
    30   include "ener.h"
    31   include "description.h"
    3227
    3328  !-------------------------------------------------------------------
  • trunk/LMDZ.COMMON/libf/dyn3dpar/bernoui_p.F

    r1019 r1422  
    2525#include "dimensions.h"
    2626#include "paramet.h"
    27 #include "logic.h"
    2827c
    2928c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3dpar/bilan_dyn_p.F

    r1300 r1422  
    1717      use misc_mod
    1818      use write_field_p
     19      USE comvert_mod, ONLY: presnivs
     20      USE comconst_mod, ONLY: cpp,pi
     21      USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn
    1922      IMPLICIT NONE
    2023
    2124#include "dimensions.h"
    2225#include "paramet.h"
    23 #include "comconst.h"
    24 #include "comvert.h"
    2526#include "comgeom2.h"
    26 #include "temps.h"
    2727#include "iniprint.h"
    2828
  • trunk/LMDZ.COMMON/libf/dyn3dpar/caldyn_p.F

    r1189 r1422  
    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 "comconst.h"
    34 #include "comvert.h"
    3534#include "comgeom.h"
    3635
  • trunk/LMDZ.COMMON/libf/dyn3dpar/ce0l.F90

    r1302 r1422  
    4242!#include "indicesol.h"
    4343#include "iniprint.h"
    44 #include "temps.h"
    45 #include "logic.h"
    4644#ifdef CPP_MPI
    4745      include 'mpif.h'
  • trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F90

    r1391 r1422  
    1919  use assert_m, only: assert
    2020  use sponge_mod_p, only: callsponge,mode_sponge,nsponge,tetasponge
     21  USE comconst_mod, ONLY: dissip_factz,dissip_deltaz,dissip_zref,               &
     22                dissip_fac_mid,dissip_fac_up,dissip_hdelta,dissip_pupstart,     &
     23                mode_top_bound,tau_top_bound,iflag_top_bound
     24  USE logic_mod, ONLY: tidal,purmats,ok_guide,read_start,iflag_phys,iflag_trac, &
     25                ok_strato,ok_gradsfile,ok_limit,ok_etat0,moyzon_mu,moyzon_ch,   &
     26                fxyhypb,ysinus
     27  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,             &
     28                alphax,alphay,taux,tauy
     29  USE temps_mod, ONLY: calend
     30
    2131  IMPLICIT NONE
    2232!-----------------------------------------------------------------------
     
    3646  include "dimensions.h"
    3747  include "paramet.h"
    38   include "logic.h"
    39   include "serre.h"
    4048  include "comdissnew.h"
    4149  include "iniprint.h"
    42   include "temps.h"
    43   include "comconst.h"
    4450
    4551! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
  • trunk/LMDZ.COMMON/libf/dyn3dpar/convmas1_p.F

    r1019 r1422  
    3232#include "dimensions.h"
    3333#include "paramet.h"
    34 #include "comvert.h"
    35 #include "logic.h"
    3634
    3735      REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm )
  • trunk/LMDZ.COMMON/libf/dyn3dpar/convmas2_p.F

    r1019 r1422  
    3232#include "dimensions.h"
    3333#include "paramet.h"
    34 #include "comvert.h"
    35 #include "logic.h"
    3634
    3735      REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm )
  • trunk/LMDZ.COMMON/libf/dyn3dpar/convmas_p.F

    r1019 r1422  
    3232#include "dimensions.h"
    3333#include "paramet.h"
    34 #include "comvert.h"
    35 #include "logic.h"
    3634
    3735      REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm )
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dissip_p.F

    r1189 r1422  
    66      USE parallel_lmdz
    77      USE write_field_p
     8      USE comconst_mod, ONLY: dtdiss
    89      IMPLICIT NONE
    910
     
    2930#include "dimensions.h"
    3031#include "paramet.h"
    31 #include "comconst.h"
    3232#include "comgeom.h"
    3333#include "comdissnew.h"
  • trunk/LMDZ.COMMON/libf/dyn3dpar/divgrad_p.F

    r1019 r1422  
    2323#include "comgeom.h"
    2424#include "comdissipn.h"
    25 #include "logic.h"
    2625c
    2726      INTEGER klevel
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dteta1_p.F

    r1019 r1422  
    2222#include "dimensions.h"
    2323#include "paramet.h"
    24 #include "logic.h"
    2524
    2625      REAL teta( ip1jmp1,llm ),pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dudv2_p.F

    r1019 r1422  
    2525#include "dimensions.h"
    2626#include "paramet.h"
    27 #include "comvert.h"
    2827
    2928      REAL teta( ip1jmp1,llm ),pkf( ip1jmp1,llm ) ,bern( ip1jmp1,llm ),
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem_p.F

    r1107 r1422  
    1111      use netcdf95, only: NF95_PUT_VAR
    1212      use control_mod, only : planet_type
     13      USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff,nivsig,nivsigs,
     14     .                  presnivs,pseudoalt
     15      USE comconst_mod, ONLY: daysec,dtvr,rad,omeg,g,cpp,kappa,pi
     16      USE logic_mod, ONLY: fxyhypb,ysinus
     17      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
     18     .                  taux,tauy
     19      USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn,itaufin,
     20     .                  start_time,hour_ini
     21      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1322
    1423      IMPLICIT NONE
     
    2029#include "dimensions.h"
    2130#include "paramet.h"
    22 #include "comconst.h"
    23 #include "comvert.h"
    2431#include "comgeom2.h"
    25 #include "temps.h"
    26 #include "ener.h"
    27 #include "logic.h"
    2832#include "netcdf.inc"
    29 #include "description.h"
    30 #include "serre.h"
    3133#include "iniprint.h"
    3234
     
    590592      use netcdf, only: NF90_get_VAR
    591593      use netcdf95, only: NF95_PUT_VAR
     594      USE temps_mod, ONLY: itau_dyn,itaufin
    592595
    593596      IMPLICIT NONE
     
    597600#include "dimensions.h"
    598601#include "paramet.h"
    599 #include "description.h"
    600602#include "netcdf.inc"
    601 #include "comvert.h"
    602603#include "comgeom.h"
    603 #include "temps.h"
    604604#include "iniprint.h"
    605605
  • trunk/LMDZ.COMMON/libf/dyn3dpar/exner_hyb_p_m.F90

    r1302 r1422  
    3333    !
    3434    USE parallel_lmdz
     35    USE comvert_mod, ONLY: preff
     36    USE comconst_mod, ONLY: jmp1,kappa,cpp,r
    3537    !
    3638    include "dimensions.h"
    3739    include "paramet.h"
    38     include "comconst.h"
    3940    include "comgeom.h"
    40     include "comvert.h"
    41     include "serre.h"
    4241
    4342    INTEGER  ngrid
  • trunk/LMDZ.COMMON/libf/dyn3dpar/exner_milieu_p_m.F90

    r1302 r1422  
    11module exner_milieu_p_m
     2
     3  USE comconst_mod, ONLY: jmp1,kappa,cpp,r
    24
    35  IMPLICIT NONE
     
    3032    !
    3133    USE parallel_lmdz
     34    USE comvert_mod, ONLY: preff
    3235    !
    3336    include "dimensions.h"
    3437    include "paramet.h"
    35     include "comconst.h"
    3638    include "comgeom.h"
    37     include "comvert.h"
    38     include "serre.h"
    3939
    4040    INTEGER  ngrid
  • trunk/LMDZ.COMMON/libf/dyn3dpar/fluxstokenc_p.F

    r1019 r1422  
    2121#include "dimensions.h"
    2222#include "paramet.h"
    23 #include "comconst.h"
    24 #include "comvert.h"
    2523#include "comgeom.h"
    2624#include "tracstoke.h"
    27 #include "temps.h"
    2825#include "iniprint.h"
    2926
  • trunk/LMDZ.COMMON/libf/dyn3dpar/friction_p.F

    r1019 r1422  
    1212      USE ioipsl_getincom
    1313#endif
     14      USE comconst_mod, ONLY: pi
    1415      IMPLICIT NONE
    1516
     
    2930#include "paramet.h"
    3031#include "comgeom2.h"
    31 #include "comconst.h"
    3232#include "iniprint.h"
    3333#include "academic.h"
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F

    r1395 r1422  
    3939      USE comgeomphy
    4040#endif
     41      USE comconst_mod, ONLY: daysec,dtvr,dtphys,rad,g,r,cpp
     42      USE logic_mod
     43      USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref,
     44     .          itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end,
     45     .          dt,hour_ini,itaufin
    4146      IMPLICIT NONE
    4247
     
    7378#include "dimensions.h"
    7479#include "paramet.h"
    75 #include "comconst.h"
    7680#include "comdissnew.h"
    77 #include "comvert.h"
    7881#include "comgeom.h"
    79 #include "logic.h"
    80 #include "temps.h"
    8182!!!!!!!!!!!#include "control.h"
    82 #include "ener.h"
    83 #include "description.h"
    84 #include "serre.h"
    8583!#include "com_io_dyn.h"
    8684#include "iniprint.h"
     
    166164      abort_message = 'last timestep reached'
    167165      modname = 'gcm'
    168       descript = 'Run GCM LMDZ'
    169166      lafin    = .FALSE.
    170167      dynhist_file = 'dyn_hist'
     
    608605!variable temps no longer exists
    609606c$OMP PARALLEL DEFAULT(SHARED)
    610 c$OMP1 COPYIN(/temps_r/,/temps_i/,/temps_c/,/logici/,/logicl/)
     607c       Copy all threadprivate variables from temps_mod
     608c$OMP1 COPYIN(dt,jD_ref,jH_ref,start_time,hour_ini,day_ini,day_end)
     609c$OMP1 COPYIN(annee_ref,day_ref,itau_dyn,itau_phy,itaufin,calend)
     610c       Copy all threadprivate variables from logic_mod
     611c$OMP1 COPYIN(purmats,forward,leapf,apphys,statcl,conser,apdiss,apdelq)
     612c$OMP1 COPYIN(saison,ecripar,fxyhypb,ysinus,read_start,ok_guide)
     613c$OMP1 COPYIN(ok_strato,tidal,ok_gradsfile,ok_limit,ok_etat0,physic)
     614c$OMP1 COPYIN(grireg,iflag_phys,iflag_trac)
     615
     616
    611617      CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,
    612618     .              time_0)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/geopot_p.F

    r1019 r1422  
    2828#include "dimensions.h"
    2929#include "paramet.h"
    30 #include "comvert.h"
    3130
    3231c   Arguments:
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gradiv_p.F

    r1019 r1422  
    2121#include "paramet.h"
    2222#include "comdissipn.h"
    23 #include "logic.h"
    2423
    2524      INTEGER klevel
  • trunk/LMDZ.COMMON/libf/dyn3dpar/groupe_p.F

    r1019 r1422  
    1616#include "dimensions.h"
    1717#include "paramet.h"
    18 #include "comconst.h"
    1918#include "comgeom2.h"
    20 #include "comvert.h"
    2119
    2220      integer ngroup
  • trunk/LMDZ.COMMON/libf/dyn3dpar/groupeun_p.F

    r1019 r1422  
    66#include "dimensions.h"
    77#include "paramet.h"
    8 #include "comconst.h"
    98#include "comgeom2.h"
    109
     
    140139#include "dimensions.h"
    141140#include "paramet.h"
    142 #include "comconst.h"
    143141#include "comgeom2.h"
    144142
  • trunk/LMDZ.COMMON/libf/dyn3dpar/guide_p_mod.F90

    r1391 r1422  
    6969
    7070    USE control_mod
     71    USE serre_mod, ONLY: grossismx
    7172
    7273    IMPLICIT NONE
     
    7576    INCLUDE "paramet.h"
    7677    INCLUDE "netcdf.inc"
    77 
    78     ! For grossismx:
    79     include "serre.h"
    8078
    8179    INTEGER                :: error,ncidpl,rid,rcod
     
    341339    USE parallel_lmdz
    342340    USE control_mod
     341    USE comvert_mod, ONLY: ap,bp,preff,presnivs,pressure_exner
     342    USE comconst_mod, ONLY: daysec,dtvr,kappa,cpp
    343343   
    344344    IMPLICIT NONE
     
    346346    INCLUDE "dimensions.h"
    347347    INCLUDE "paramet.h"
    348     INCLUDE "comconst.h"
    349     INCLUDE "comvert.h"
    350348
    351349    ! Variables entree
     
    619617  SUBROUTINE guide_zonave(typ,hsize,vsize,field)
    620618
     619    USE comconst_mod, ONLY: pi
     620
    621621    IMPLICIT NONE
    622622
     
    624624    INCLUDE "paramet.h"
    625625    INCLUDE "comgeom.h"
    626     INCLUDE "comconst.h"
    627626   
    628627    ! input/output variables
     
    707706  USE mod_hallo
    708707  USE Bands
     708  USE comvert_mod, ONLY: ap,bp,preff,pressure_exner
     709  USE comconst_mod, ONLY: kappa,cpp
    709710  IMPLICIT NONE
    710711
    711712  include "dimensions.h"
    712713  include "paramet.h"
    713   include "comvert.h"
    714714  include "comgeom2.h"
    715   include "comconst.h"
    716715
    717716  REAL, DIMENSION (iip1,jjp1),     INTENT(IN) :: psi ! Psol gcm
     
    10991098! Calcul des constantes de rappel alpha (=1/tau)
    11001099
     1100    USE comconst_mod, ONLY: pi
     1101    USE serre_mod, ONLY: clon,clat,grossismx,grossismy
     1102
    11011103    implicit none
    11021104
    11031105    include "dimensions.h"
    11041106    include "paramet.h"
    1105     include "comconst.h"
    11061107    include "comgeom2.h"
    1107     include "serre.h"
    11081108
    11091109! input arguments :
     
    18131813  SUBROUTINE guide_out(varname,hsize,vsize,field,factt)
    18141814    USE parallel_lmdz
     1815    USE comvert_mod, ONLY: presnivs
     1816    USE comconst_mod, ONLY: pi
    18151817    IMPLICIT NONE
    18161818
     
    18191821    INCLUDE "netcdf.inc"
    18201822    INCLUDE "comgeom2.h"
    1821     INCLUDE "comconst.h"
    1822     INCLUDE "comvert.h"
    18231823   
    18241824    ! Variables entree
  • trunk/LMDZ.COMMON/libf/dyn3dpar/initdynav_p.F

    r1019 r1422  
    1212       use misc_mod
    1313       USE infotrac
     14       USE comvert_mod, ONLY: nivsigs
     15       USE comconst_mod, ONLY: pi
     16       USE temps_mod, ONLY: itau_dyn
    1417
    1518      implicit none
     
    4346#include "dimensions.h"
    4447#include "paramet.h"
    45 #include "comconst.h"
    46 #include "comvert.h"
    4748#include "comgeom.h"
    48 #include "temps.h"
    49 #include "ener.h"
    50 #include "logic.h"
    51 #include "description.h"
    52 #include "serre.h"
    5349#include "iniprint.h"
    5450
  • trunk/LMDZ.COMMON/libf/dyn3dpar/initfluxsto_p.F

    r1019 r1422  
    1313       use Write_field
    1414       use misc_mod
     15       USE comvert_mod, ONLY: nivsigs
     16       USE comconst_mod, ONLY: pi
     17       USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn
    1518       
    1619      implicit none
     
    4548#include "dimensions.h"
    4649#include "paramet.h"
    47 #include "comconst.h"
    48 #include "comvert.h"
    4950#include "comgeom.h"
    50 #include "temps.h"
    51 #include "ener.h"
    52 #include "logic.h"
    53 #include "description.h"
    54 #include "serre.h"
    5551#include "iniprint.h"
    5652
  • trunk/LMDZ.COMMON/libf/dyn3dpar/inithist_p.F

    r1019 r1422  
    1313       use misc_mod
    1414       USE infotrac
     15       USE comvert_mod, ONLY: nivsigs
     16       USE comconst_mod, ONLY: pi
     17       USE temps_mod, ONLY: itau_dyn
    1518
    1619      implicit none
     
    4548#include "dimensions.h"
    4649#include "paramet.h"
    47 #include "comconst.h"
    48 #include "comvert.h"
    4950#include "comgeom.h"
    50 #include "temps.h"
    51 #include "ener.h"
    52 #include "logic.h"
    53 #include "description.h"
    54 #include "serre.h"
    5551#include "iniprint.h"
    5652
  • trunk/LMDZ.COMMON/libf/dyn3dpar/integrd_p.F

    r1391 r1422  
    77      USE parallel_lmdz
    88      USE control_mod, only : planet_type
     9      USE comvert_mod, ONLY: ap,bp
     10      USE comconst_mod, ONLY: pi
     11      USE logic_mod, ONLY: leapf
     12      USE temps_mod, ONLY: dt
    913      IMPLICIT NONE
    1014
     
    2731#include "dimensions.h"
    2832#include "paramet.h"
    29 #include "comconst.h"
    3033#include "comgeom.h"
    31 #include "comvert.h"
    32 #include "logic.h"
    33 #include "temps.h"
    34 #include "serre.h"
    3534#include "iniprint.h"
    3635
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r1403 r1422  
    3333       use sponge_mod_p, only: callsponge,mode_sponge,sponge_p
    3434       use comuforc_h
     35       USE comvert_mod, ONLY: ap,bp,pressure_exner,presnivs
     36       USE comconst_mod, ONLY: jmp1,daysec,dtvr,dtphys,dtdiss,
     37     .                  cpp,ihf,iflag_top_bound,pi
     38       USE logic_mod, ONLY: iflag_phys,ok_guide,forward,leapf,apphys,
     39     .                  statcl,conser,apdiss,purmats,tidal,ok_strato
     40       USE temps_mod, ONLY: itaufin,jD_ref,jH_ref,day_ini,
     41     .                  day_ref,start_time,dt
     42
    3543
    3644      IMPLICIT NONE
     
    6977#include "dimensions.h"
    7078#include "paramet.h"
    71 #include "comconst.h"
    7279#include "comdissnew.h"
    73 #include "comvert.h"
    7480#include "comgeom.h"
    75 #include "logic.h"
    76 #include "temps.h"
    77 #include "ener.h"
    78 #include "description.h"
    79 #include "serre.h"
    8081!#include "com_io_dyn.h"
    8182#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/dyn3dpar/massbar_p.F

    r1019 r1422  
    1818#include "dimensions.h"
    1919#include "paramet.h"
    20 #include "comconst.h"
    2120#include "comgeom.h"
    2221c
  • trunk/LMDZ.COMMON/libf/dyn3dpar/massbarxy_p.F

    r1019 r1422  
    1717#include "dimensions.h"
    1818#include "paramet.h"
    19 #include "comconst.h"
    2019#include "comgeom.h"
    2120c
  • trunk/LMDZ.COMMON/libf/dyn3dpar/massdair_p.F

    r1019 r1422  
    1818#include "dimensions.h"
    1919#include "paramet.h"
    20 #include "comconst.h"
    2120#include "comgeom.h"
    2221c
  • trunk/LMDZ.COMMON/libf/dyn3dpar/nxgrarot_p.F

    r1019 r1422  
    2222#include "paramet.h"
    2323#include "comdissipn.h"
    24 #include "logic.h"
    2524c
    2625      INTEGER klevel
  • trunk/LMDZ.COMMON/libf/dyn3dpar/qminimum_p.F

    r1019 r1422  
    11      SUBROUTINE qminimum_p( q,nq,deltap )
    22      USE parallel_lmdz
     3      USE comvert_mod, ONLY: presnivs
    34      IMPLICIT none
    45c
     
    89#include "dimensions.h"
    910#include "paramet.h"
    10 #include "comvert.h"
    1111c
    1212      INTEGER nq
  • trunk/LMDZ.COMMON/libf/dyn3dpar/sponge_mod_p.F90

    r1315 r1422  
    11module sponge_mod_p
     2
     3USE comvert_mod, ONLY: ap,bp,preff,scaleheight
    24
    35implicit none
     
    3638#include "paramet.h"
    3739#include "comdissip.h"
    38 #include "comvert.h"
    3940#include "comgeom2.h"
    4041#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/dyn3dpar/sw_case_williamson91_6.F

    r1 r1422  
    2626c
    2727c=======================================================================
     28      USE comvert_mod, ONLY: ap,bp,preff
     29      USE comconst_mod, ONLY: cpp,omeg,rad
     30
    2831      IMPLICIT NONE
    2932c-----------------------------------------------------------------------
     
    3336#include "dimensions.h"
    3437#include "paramet.h"
    35 #include "comvert.h"
    36 #include "comconst.h"
    3738#include "comgeom.h"
    3839#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/dyn3dpar/top_bound_p.F

    r1019 r1422  
    44      SUBROUTINE top_bound_p(vcov,ucov,teta,masse,dt,ducov)
    55      USE parallel_lmdz
     6      USE comvert_mod, ONLY: presnivs,preff,scaleheight
     7      USE comconst_mod, ONLY: iflag_top_bound,tau_top_bound,
     8     .                  mode_top_bound
    69      IMPLICIT NONE
    710c
    811#include "dimensions.h"
    912#include "paramet.h"
    10 #include "comconst.h"
    11 #include "comvert.h"
    1213#include "comgeom2.h"
    1314
  • trunk/LMDZ.COMMON/libf/dyn3dpar/tourpot_p.F

    r1019 r1422  
    2323#include "paramet.h"
    2424#include "comgeom.h"
    25 #include "logic.h"
    2625
    2726      REAL  rot( ip1jm,llm )
  • trunk/LMDZ.COMMON/libf/dyn3dpar/vitvert_p.F

    r1019 r1422  
    22c
    33      USE parallel_lmdz
     4      USE comvert_mod, ONLY: bp
    45      IMPLICIT NONE
    56
     
    2829#include "dimensions.h"
    2930#include "paramet.h"
    30 #include "comvert.h"
    3131
    3232      REAL w(ip1jmp1,llm),convm(ip1jmp1,llm)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/vlsplt_p.F

    r1019 r1422  
    2121#include "dimensions.h"
    2222#include "paramet.h"
    23 #include "logic.h"
    24 #include "comvert.h"
    25 #include "comconst.h"
    2623
    2724c
     
    204201#include "dimensions.h"
    205202#include "paramet.h"
    206 #include "logic.h"
    207 #include "comvert.h"
    208 #include "comconst.h"
    209203c
    210204c
     
    535529c   --------------------------------------------------------------------
    536530      USE parallel_lmdz
     531      USE comconst_mod, ONLY: pi
     532
    537533      IMPLICIT NONE
    538534c
    539535#include "dimensions.h"
    540536#include "paramet.h"
    541 #include "logic.h"
    542 #include "comvert.h"
    543 #include "comconst.h"
    544537#include "comgeom.h"
    545538c
     
    928921#include "dimensions.h"
    929922#include "paramet.h"
    930 #include "logic.h"
    931 #include "comvert.h"
    932 #include "comconst.h"
    933923c
    934924c
  • trunk/LMDZ.COMMON/libf/dyn3dpar/vlspltgen_p.F

    r1019 r1422  
    2727      USE VAMPIR
    2828      USE infotrac, ONLY : nqtot
     29      USE comconst_mod, ONLY: cpp
    2930      IMPLICIT NONE
    3031
     
    3233#include "dimensions.h"
    3334#include "paramet.h"
    34 #include "logic.h"
    35 #include "comvert.h"
    36 #include "comconst.h"
    3735
    3836c
  • trunk/LMDZ.COMMON/libf/dyn3dpar/vlspltqs_p.F

    r1086 r1422  
    3131#include "dimensions.h"
    3232#include "paramet.h"
    33 #include "logic.h"
    34 #include "comvert.h"
    35 #include "comconst.h"
    3633
    3734c
     
    245242#include "dimensions.h"
    246243#include "paramet.h"
    247 #include "logic.h"
    248 #include "comvert.h"
    249 #include "comconst.h"
    250244c
    251245c
     
    593587c   --------------------------------------------------------------------
    594588      USE parallel_lmdz
     589      USE comconst_mod, ONLY: pi
    595590      IMPLICIT NONE
    596591c
    597592#include "dimensions.h"
    598593#include "paramet.h"
    599 #include "logic.h"
    600 #include "comvert.h"
    601 #include "comconst.h"
    602594#include "comgeom.h"
    603595c
  • trunk/LMDZ.COMMON/libf/dyn3dpar/writedynav_p.F

    r1019 r1422  
    1212      USE misc_mod
    1313      USE infotrac
     14      USE comconst_mod, ONLY: cpp
     15      USE temps_mod, ONLY: itau_dyn
    1416      implicit none
    1517
     
    4244#include "dimensions.h"
    4345#include "paramet.h"
    44 #include "comconst.h"
    45 #include "comvert.h"
    4646#include "comgeom.h"
    47 #include "temps.h"
    48 #include "ener.h"
    49 #include "logic.h"
    50 #include "description.h"
    51 #include "serre.h"
    5247#include "iniprint.h"
    5348
  • trunk/LMDZ.COMMON/libf/dyn3dpar/writehist_p.F

    r1019 r1422  
    1212      USE misc_mod
    1313      USE infotrac
     14      USE temps_mod, ONLY: itau_dyn
    1415      implicit none
    1516
     
    4344#include "dimensions.h"
    4445#include "paramet.h"
    45 #include "comconst.h"
    46 #include "comvert.h"
    4746#include "comgeom.h"
    48 #include "temps.h"
    49 #include "ener.h"
    50 #include "logic.h"
    51 #include "description.h"
    52 #include "serre.h"
    5347#include "iniprint.h"
    5448
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/calfis.F

    r1403 r1422  
    3636! used only for zonal averages
    3737      USE moyzon_mod
     38      USE comvert_mod, ONLY: presnivs,preff
     39      USE comconst_mod, ONLY: daysec,dtvr,dtphys,kappa,cpp,g,rad,pi
     40      USE logic_mod, ONLY: moyzon_ch,moyzon_mu
    3841
    3942      IMPLICIT NONE
     
    9396#include "dimensions.h"
    9497#include "paramet.h"
    95 #include "temps.h"
    96 #include "logic.h"
    9798
    9899      INTEGER ngridmx
    99100      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    100101
    101 #include "comconst.h"
    102 #include "comvert.h"
    103102#include "comgeom2.h"
    104103#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/calfis_p.F

    r1403 r1422  
    4444      USE infotrac, ONLY: nqtot, niadv, tname
    4545      USE control_mod, ONLY: planet_type, nsplit_phys
     46      USE comvert_mod, ONLY: preff,presnivs
     47      USE comconst_mod, ONLY: daysec,dtvr,dtphys,kappa,cpp,g,rad,pi
     48      USE logic_mod, ONLY: moyzon_ch,moyzon_mu
    4649
    4750      IMPLICIT NONE
     
    102105#include "dimensions.h"
    103106#include "paramet.h"
    104 #include "temps.h"
    105 #include "logic.h"
    106107
    107108      INTEGER ngridmx
    108109      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    109110
    110 #include "comconst.h"
    111 #include "comvert.h"
    112111#include "comgeom2.h"
    113112#include "iniprint.h"
  • trunk/LMDZ.COMMON/libf/filtrez/filtreg_mod.F90

    r1019 r1422  
    1414  USE mod_filtre_fft_loc, ONLY : Init_filtre_fft_loc=>Init_filtre_fft    !
    1515#endif
     16  USE logic_mod, ONLY: fxyhypb,ysinus
     17  USE serre_mod, ONLY: alphax
    1618    !    ... H. Upadhyaya, O.Sharma   ...
    1719    !
     
    2729#include "comgeom.h"
    2830#include "coefils.h"
    29 #include "logic.h"
    30 #include "serre.h"
    3131
    3232    REAL  dlonu(iim),dlatu(jjm)
  • trunk/LMDZ.COMMON/libf/filtrez/inifgn.F

    r1 r1422  
    1111#include "paramet.h"
    1212#include "comgeom.h"
    13 #include "serre.h"
    1413
    1514c
Note: See TracChangeset for help on using the changeset viewer.