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/dyn3d_common
Files:
4 added
54 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.