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
Files:
2 added
25 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
Note: See TracChangeset for help on using the changeset viewer.