Changeset 1397


Ignore:
Timestamp:
Mar 13, 2015, 9:17:42 AM (10 years ago)
Author:
milmd
Message:

In LMDZ.GENERIC replacement of all phystd .h files by module files.

Location:
trunk
Files:
5 added
6 deleted
49 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d_common/diagedyn.F

    r1300 r1397  
    5353c======================================================================
    5454 
     55      USE cpdet_phy_mod, ONLY: cpdet,tpot2t
     56
    5557      IMPLICIT NONE
    5658C
     
    139141     $        , h_qs_pre, qw_pre, ql_pre, qs_pre , ec_pre
    140142
    141 
    142       real,external :: cpdet
    143143
    144144#ifdef CPP_EARTH
  • trunk/LMDZ.GENERIC/libf/dyn3d/disvert.F

    r830 r1397  
    33! to use  'getin'
    44      USE ioipsl_getincom
     5      USE callkeys_mod, ONLY: kastprof,pceil
    56
    67c    Auteur :  F. Forget Y. Wanherdrick, P. Levan
     
    1415#include "comconst.h"
    1516#include "logic.h"
    16 
    17 #include "callkeys.h"
    1817
    1918
  • trunk/LMDZ.GENERIC/libf/phystd/aeropacity.F90

    r1384 r1397  
    77       USE tracer_h, only: noms,rho_co2,rho_ice
    88       use comcstfi_mod, only: g
     9       use callkeys_mod, only: aerofixco2,aerofixh2o,kastprof,cloudlvl, &
     10                CLFvarying,CLFfixval,dusttau,                           &
     11                pres_bottom_tropo,pres_top_tropo,obs_tau_col_tropo,     &
     12                pres_bottom_strato,pres_top_strato,obs_tau_col_strato
    913                 
    1014       implicit none
     
    4145!=======================================================================
    4246
    43 #include "callkeys.h"
    44 
    4547      INTEGER,INTENT(IN) :: ngrid  ! number of atmospheric columns
    4648      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
  • trunk/LMDZ.GENERIC/libf/phystd/aeroptproperties.F90

    r1315 r1397  
    3434!#include "dimensions.h"
    3535!#include "dimphys.h"
    36 #include "callkeys.h"
    3736
    3837!     Local variables
  • trunk/LMDZ.GENERIC/libf/phystd/ave_stelspec.F90

    r1325 r1397  
    2626      use radcommon_h, only: BWNV, DWNV, tstellar
    2727      use datafile_mod, only: datadir
     28      use callkeys_mod, only: stelbbody,stelTbb,startype
    2829
    2930      implicit none
    30 
    31 #include "callkeys.h"
    3231
    3332      real*8 STELLAR(L_NSPECTV)
  • trunk/LMDZ.GENERIC/libf/phystd/calc_cpp3d.F90

    r1384 r1397  
    1515      implicit none
    1616
    17 #include "callkeys.h"
    18 #include "cpdet.h"
    19 
    2017      !real cp0, dB2dT2
    2118      real cppNI      ! specific heat capacity at const. pressure
  • trunk/LMDZ.GENERIC/libf/phystd/calc_cpp_mugaz.F90

    r1384 r1397  
    1919      use gases_h
    2020      use comcstfi_mod, only: cpp, mugaz
     21      use callkeys_mod, only: check_cpp_match,force_cpp
    2122      implicit none
    22 
    23 #include "callkeys.h"
    2423
    2524      real cpp_c   
  • trunk/LMDZ.GENERIC/libf/phystd/calc_rayleigh.F90

    r1384 r1397  
    3131
    3232      implicit none
    33 
    34 #include "callkeys.h"
    3533
    3634      real*8 wl
  • trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90

    r1384 r1397  
    1919      USE tracer_h
    2020      use comcstfi_mod, only: pi, mugaz, cpp
     21      use callkeys_mod, only: varactive,diurnal,tracer,water,nosurf,varfixed,satval,    &
     22                kastprof,strictboundcorrk,specOLR,CLFvarying
    2123
    2224      implicit none
     
    3638!
    3739!==================================================================
    38 
    39 #include "callkeys.h"
    4040
    4141!-----------------------------------------------------------------------
  • trunk/LMDZ.GENERIC/libf/phystd/callsedim.F

    r1384 r1397  
    88      USE tracer_h, only : igcm_co2_ice,igcm_h2o_ice,radius,rho_q
    99      use comcstfi_mod, only: g
     10      use callkeys_mod, only : water
    1011
    1112      IMPLICIT NONE
     
    2829c   declarations:
    2930c   -------------
    30 
    31 #include "callkeys.h"
    3231
    3332c   arguments:
  • trunk/LMDZ.GENERIC/libf/phystd/condense_cloud.F90

    r1384 r1397  
    5656!==================================================================
    5757
    58 #include "callkeys.h"
    59 
    6058!-----------------------------------------------------------------------
    6159!     Arguments
     
    482480      implicit none
    483481
    484 #include "callkeys.h"
    485 
    486482      real p, peff, tcond
    487483      real, parameter :: ptriple=518000.0
     
    507503!     (JL 2011)
    508504
     505      use callkeys_mod, only: co2supsat
     506
    509507      implicit none
    510 
    511 #include "callkeys.h"
    512508
    513509      real p, peff, tnuc
  • trunk/LMDZ.GENERIC/libf/phystd/convadj.F

    r1384 r1397  
    88      USE tracer_h
    99      use comcstfi_mod, only: g
     10      use callkeys_mod, only: tracer,water
    1011
    1112      implicit none
     
    2930!     Declarations
    3031!     ------------
    31 
    32 #include "callkeys.h"
    3332
    3433
  • trunk/LMDZ.GENERIC/libf/phystd/hydrol.F90

    r1384 r1397  
    1212  USE tracer_h
    1313  use slab_ice_h
     14  use callkeys_mod, only: albedosnow,ok_slab_ocean,Tsaldiff,maxicethick,co2cond
    1415
    1516  implicit none
     
    3940!     
    4041!==================================================================
    41 
    42 #include "callkeys.h"
    4342
    4443      integer ngrid,nq
  • trunk/LMDZ.GENERIC/libf/phystd/iniaerosol.F

    r1151 r1397  
    44      use radinc_h, only: naerkind
    55      use aerosol_mod
     6      use callkeys_mod, only: aeroco2,aeroh2o,dusttau,aeroh2so4,
     7     &          aeroback2lay
    68
    79      IMPLICIT NONE
     
    1719c=======================================================================
    1820
    19 
    20 #include "callkeys.h"
    2121      integer ia
    2222
  • trunk/LMDZ.GENERIC/libf/phystd/inifis.F

    r1384 r1397  
    1414      use planete_mod, only: nres
    1515      use planetwide_mod, only: planetwide_sumval
     16      use callkeys_mod
    1617
    1718!=======================================================================
     
    5556      USE ioipsl_getincom_p
    5657      IMPLICIT NONE
    57 
    58 #include "callkeys.h"
    5958
    6059
     
    106105     &     ,iostat=ierr)
    107106      CLOSE(99)
    108       IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys.h
     107      IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys_mod module
    109108!$OMP END MASTER
    110109!$OMP BARRIER
  • trunk/LMDZ.GENERIC/libf/phystd/inistats.F

    r1216 r1397  
    22
    33      use mod_phys_lmdz_para, only : is_master
     4      use statto_mod, only: istats,istime
    45      implicit none
    56
     
    910#include "comvert.h"
    1011#include "comconst.h"
    11 #include "statto.h"
    1212#include "netcdf.inc"
    1313
  • trunk/LMDZ.GENERIC/libf/phystd/initracer.F

    r1384 r1397  
    44      USE comgeomfi_h
    55      USE tracer_h
     6      USE callkeys_mod, only: water
    67      IMPLICIT NONE
    78c=======================================================================
     
    2425
    2526#include "dimensions.h"
    26 #include "callkeys.h"
    2727
    2828      integer :: ngrid,nq
  • trunk/LMDZ.GENERIC/libf/phystd/kcm1d.F90

    r1384 r1397  
    3232#include "dimensions.h"
    3333!#include "dimphys.h"
    34 #include "callkeys.h"
    3534
    3635  ! --------------------------------------------------------------
  • trunk/LMDZ.GENERIC/libf/phystd/kcmprof_fn.F90

    r1384 r1397  
    55use gases_h
    66use comcstfi_mod, only: mugaz, cpp, g
     7use callkeys_mod, only: co2cond
    78implicit none
    89
     
    1213!     Authour: Adapted from a code by E. Marcq by R. Wordsworth (2011)
    1314!     ----------------------------------------------------------------
    14 
    15 #include "callkeys.h"
    1615
    1716  integer ilay, nlay
  • trunk/LMDZ.GENERIC/libf/phystd/largescale.F90

    r1384 r1397  
    2323!     
    2424!==================================================================
    25 
    26 #include "callkeys.h"
    2725
    2826      INTEGER ngrid,nlayer,nq
  • trunk/LMDZ.GENERIC/libf/phystd/lect_start_archive.F

    r1308 r1397  
    1212!      USE control_mod
    1313! to use  'getin'
     14      USE callkeys_mod, ONLY: ok_slab_ocean
    1415
    1516c=======================================================================
     
    4344#include "netcdf.inc"
    4445!#include"advtrac.h"
    45 #include "callkeys.h"
    4646c=======================================================================
    4747c   Declarations
  • trunk/LMDZ.GENERIC/libf/phystd/mass_redistribution.F90

    r1384 r1397  
    1111       USE planete_mod, only: bp
    1212       use comcstfi_mod, only: g
     13       USE callkeys_mod, ONLY: water
    1314       
    1415       IMPLICIT NONE
     
    5152!    0.  Declarations :
    5253!    ------------------
    53 !
    54 #include "callkeys.h"
    5554
    5655!-----------------------------------------------------------------------
  • trunk/LMDZ.GENERIC/libf/phystd/mkstat.F90

    r1348 r1397  
    1111
    1212use mod_phys_lmdz_para, only : is_master
     13use statto_mod, only: istime,count
    1314
    1415implicit none
    1516
    1617#include "dimensions.h"
    17 #include "statto.h"
    1818#include "netcdf.inc"
    1919
  • trunk/LMDZ.GENERIC/libf/phystd/newtrelax.F90

    r1384 r1397  
    22       
    33  use comcstfi_mod, only: rcp, pi
     4  use callkeys_mod, only: tau_relax
    45  implicit none
    56
    6 #include "callkeys.h"
    77#include "netcdf.inc"
    88
  • trunk/LMDZ.GENERIC/libf/phystd/ocean_slab_mod.F90

    r1384 r1397  
    1313      use surf_heat_transp_mod
    1414      implicit none
    15 
    16 
    17 #include "callkeys.h"
    1815
    1916
     
    6461
    6562
    66 #include "callkeys.h"
    67 
    68 
    6963
    7064
     
    203197
    204198      use slab_ice_h
    205 
    206 #include "callkeys.h"
    207 
     199      use callkeys_mod, only: ok_slab_sic
    208200
    209201
     
    441433
    442434    use slab_ice_h
    443 
    444 #include "callkeys.h"
     435    use callkeys_mod, only: ok_slab_sic,ok_slab_heat_transp
    445436
    446437! Input arguments
  • trunk/LMDZ.GENERIC/libf/phystd/optci.F90

    r1384 r1397  
    77  use gases_h
    88  use comcstfi_mod, only: g, r, mugaz
     9  use callkeys_mod, only: kastprof,continuum,graybody,H2Ocont_simple
    910  implicit none
    1011
     
    2930  !==================================================================
    3031
    31 #include "callkeys.h"
    32 
    3332
    3433  real*8 DTAUI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
  • trunk/LMDZ.GENERIC/libf/phystd/optcv.F90

    r1384 r1397  
    77  use gases_h
    88  use comcstfi_mod, only: g, r, mugaz
     9  use callkeys_mod, only: kastprof,continuum,graybody,H2Ocont_simple,callgasvis
    910
    1011  implicit none
     
    3536  !     
    3637  !-------------------------------------------------------------------
    37 
    38 #include "callkeys.h"
    3938
    4039
  • trunk/LMDZ.GENERIC/libf/phystd/phyredem.F90

    r1384 r1397  
    144144  use infotrac, only: tname
    145145  use slab_ice_h, only: noceanmx
     146  use callkeys_mod, only: ok_slab_ocean
    146147
    147148  implicit none
    148 !======================================================================
    149 #include "callkeys.h"
    150 !======================================================================
     149
    151150  character(len=*),intent(in) :: filename
    152151  integer,intent(in) :: nsoil
  • trunk/LMDZ.GENERIC/libf/phystd/physiq.F90

    r1384 r1397  
    3535                            obliquit, nres, z0
    3636      use comcstfi_mod, only: pi, g, rcp, r, rad, mugaz, cpp, daysec
     37      use callkeys_mod
    3738      implicit none
    3839
     
    132133!    ------------------
    133134
    134 #include "callkeys.h"
    135135#include "netcdf.inc"
    136136
  • trunk/LMDZ.GENERIC/libf/phystd/radii_mod.F90

    r1384 r1397  
    77     
    88!     water cloud optical properties
     9
     10      use callkeys_mod, only: radfixed,Nmix_co2,                        &
     11                pres_bottom_tropo,pres_top_tropo,size_tropo,    &
     12                pres_bottom_strato,size_strato
    913     
    1014      real, save ::  rad_h2o
     
    4044      Implicit none
    4145
    42       include "callkeys.h"
    4346!      include "dimensions.h"
    4447!      include "dimphys.h"
     
    144147      use comcstfi_mod, only: pi
    145148      Implicit none
    146 
    147       include "callkeys.h"
    148149
    149150      integer,intent(in) :: ngrid
     
    204205      Implicit none
    205206
    206       include "callkeys.h"
    207 
    208207      integer,intent(in) :: ngrid
    209208      integer,intent(in) :: nlayer
     
    251250      Implicit none
    252251
    253       include "callkeys.h"
    254 
    255252      integer,intent(in) :: ngrid,nlayer,nq
    256253
     
    344341      use aerosol_mod   !! Particle sizes and boundaries of aerosol layers defined there
    345342     Implicit none
    346 
    347      include "callkeys.h"
    348343
    349344      integer,intent(in) :: ngrid
  • trunk/LMDZ.GENERIC/libf/phystd/rain.F90

    r1384 r1397  
    2424!     
    2525!==================================================================
    26 
    27   include "callkeys.h"
    2826
    2927!     Arguments
  • trunk/LMDZ.GENERIC/libf/phystd/rcm1d.F

    r1384 r1397  
    2121      use comcstfi_mod, only: pi, cpp, daysec, dtphys, rad, g, r,
    2222     &                        mugaz, rcp, omeg
     23      use callkeys_mod, only: tracer,check_cpp_match,rings_shadow,
     24     &          specOLR,water,pceil,ok_slab_ocean
    2325      implicit none
    2426
     
    5052#include "paramet.h"
    5153!include "dimphys.h"
    52 #include "callkeys.h"
    5354#include "comvert.h"
    5455#include "netcdf.inc"
  • trunk/LMDZ.GENERIC/libf/phystd/setspi.F90

    r1384 r1397  
    2828
    2929      implicit none
    30 
    31 #include "callkeys.h"
    3230
    3331      logical file_ok
  • trunk/LMDZ.GENERIC/libf/phystd/setspv.F90

    r1384 r1397  
    2727                             STELLARF,TAURAY
    2828      use datafile_mod, only: datadir
     29      use callkeys_mod, only: Fat1AU,rayleigh
    2930
    3031      implicit none
    31 
    32 #include "callkeys.h"
    3332
    3433      logical file_ok
  • trunk/LMDZ.GENERIC/libf/phystd/start2archive.F

    r1316 r1397  
    2828      USE ioipsl_getincom
    2929      USE planete_mod, only: year_day
     30      USE callkeys_mod, ONLY: ok_slab_ocean
    3031
    3132      implicit none
     
    4748!#include"advtrac.h"
    4849#include "netcdf.inc"
    49 #include "callkeys.h"
    5050c-----------------------------------------------------------------------
    5151c   Declarations
  • trunk/LMDZ.GENERIC/libf/phystd/su_watercycle.F90

    r1384 r1397  
    44      use comcstfi_mod, only: cpp, mugaz
    55      implicit none
    6 
    7 #include "callkeys.h"
    86
    97
  • trunk/LMDZ.GENERIC/libf/phystd/suaer_corrk.F90

    r1315 r1397  
    1111      use radcommon_h, only: qrefvis,qrefir,omegarefvis,omegarefir
    1212      use aerosol_mod
     13      use callkeys_mod, only: tplanet
    1314
    1415      implicit none
     
    4445!==================================================================
    4546
    46 #include "callkeys.h"
    4747!     Optical properties (read in external ASCII files)
    4848      INTEGER,SAVE      :: nwvl  ! Number of wavelengths in
  • trunk/LMDZ.GENERIC/libf/phystd/sugas_corrk.F90

    r1384 r1397  
    3030!      use ioipsl_getincom
    3131      use ioipsl_getincom_p
     32      use callkeys_mod, only: varactive,varfixed,graybody,callgasvis,&
     33                continuum,H2Ocont_simple
    3234      implicit none
    33 
    34 #include "callkeys.h"
    3535
    3636!==================================================================
  • trunk/LMDZ.GENERIC/libf/phystd/surf_heat_transp_mod.F90

    r1384 r1397  
    99      SUBROUTINE divgrad_phy(ngrid,nlevs,temp,delta)
    1010
    11 
     11      USE comhdiff_mod, ONLY: zmasqu,zmasqv
    1212
    1313      IMPLICIT NONE
     
    1717#include "paramet.h"
    1818#include "comgeom.h"
    19 #include "comhdiff.h"
    2019     
    2120      INTEGER,INTENT(IN) :: ngrid, nlevs
     
    4443
    4544      SUBROUTINE init_masquv(ngrid,zmasq)
     45
     46      USE comhdiff_mod, ONLY: zmasqu,zmasqv,unsfu,unsfv,unseu,unsev
    4647     
    4748      IMPLICIT NONE
     
    5152#include "paramet.h"
    5253#include "comgeom.h"
    53 #include "comhdiff.h"
    5454
    5555
     
    107107 
    108108          use slab_ice_h
     109          USE comhdiff_mod, ONLY: zmasqu,zmasqv,unsfu,unsfv,unseu,unsev
    109110
    110111      IMPLICIT NONE
     
    113114!#include "dimphys.h"
    114115#include "paramet.h"
    115 #include "callkeys.h"
    116116#include "comgeom.h"
    117 #include "comhdiff.h"
    118117
    119118      INTEGER,INTENT(IN) :: ngrid
  • trunk/LMDZ.GENERIC/libf/phystd/surface_nature.F

    r1384 r1397  
    3333!==================================================================
    3434
    35 #include "callkeys.h"
    36 
    3735        integer ngrid,nq
    3836
  • trunk/LMDZ.GENERIC/libf/phystd/surfini.F

    r1308 r1397  
    1717!#include "dimensions.h"
    1818!#include "dimphys.h"
    19 #include "callkeys.h"
    2019c
    2120      INTEGER,INTENT(IN) :: ngrid
  • trunk/LMDZ.GENERIC/libf/phystd/tabfi.F

    r1384 r1397  
    5555      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, dtphys,
    5656     &                        daysec, r
     57      use callkeys_mod, only: check_cpp_match,force_cpp
    5758      implicit none
    5859 
    5960#include "netcdf.inc"
    60 #include "callkeys.h"
    6161
    6262c-----------------------------------------------------------------------
  • trunk/LMDZ.GENERIC/libf/phystd/totalcloudfrac.F90

    r1384 r1397  
    55      USE comgeomfi_h
    66      USE tracer_h, only: igcm_h2o_ice
     7      USE callkeys_mod, ONLY: CLFfixval
    78      implicit none
    89
     
    1819!     
    1920!==================================================================
    20 
    21 #include "callkeys.h"
    2221
    2322      integer,intent(in) :: ngrid        ! number of atmospheric columns
  • trunk/LMDZ.GENERIC/libf/phystd/turbdiff.F90

    r1384 r1397  
    1212      use tracer_h, only: igcm_h2o_vap, igcm_h2o_ice
    1313      use comcstfi_mod, only: rcp, g, r, cpp
     14      use callkeys_mod, only: water,tracer,nosurf
    1415
    1516      implicit none
     
    4142!     declarations
    4243!     ------------
    43 
    44       include "callkeys.h"
    4544
    4645!     arguments
  • trunk/LMDZ.GENERIC/libf/phystd/vdifc.F

    r1384 r1397  
    1313      USE tracer_h
    1414      use comcstfi_mod, only: g, r, cpp, rcp
     15      use callkeys_mod, only: water,tracer,nosurf
    1516
    1617      implicit none
     
    3940!     ------------
    4041
    41 #include "callkeys.h"
    4242
    4343!     arguments
  • trunk/LMDZ.GENERIC/libf/phystd/writediagspecIR.F

    r1315 r1397  
    4949#endif
    5050      use control_mod, only: ecritphy, iphysiq, day_step
     51      use callkeys_mod, only: iradia
    5152
    5253      implicit none
     
    6162#include "netcdf.inc"
    6263#include "temps.h"
    63 #include "callkeys.h"
    6464
    6565! Arguments on input:
  • trunk/LMDZ.GENERIC/libf/phystd/writediagspecVI.F

    r1315 r1397  
    4949#endif
    5050      use control_mod, only: ecritphy, iphysiq, day_step
     51      use callkeys_mod, only: iradia
    5152
    5253      implicit none
     
    6162#include "netcdf.inc"
    6263#include "temps.h"
    63 #include "callkeys.h"
    6464
    6565! Arguments on input:
  • trunk/LMDZ.GENERIC/libf/phystd/writeg1d.F

    r1384 r1397  
    11      SUBROUTINE writeg1d(ngrid,nx,x,nom,titre)
     2      USE comg1d_mod, ONLY: g1d_nomfich,g1d_premier,g1d_unitfich,
     3     &  g1d_irec,g1d_nvar,g1d_nomvar,g1d_titrevar,g1d_dimvar,g1d_nlayer
    24      IMPLICIT NONE
    35
     
    1820c.......................................................................
    1921c
    20 #include "comg1d.h"
    2122
    2223c
     
    129130      SUBROUTINE endg1d(ngrid,nlayer,zlayer,ndt)
    130131      USE comcstfi_mod, ONLY: dtphys, daysec
     132      USE comg1d_mod, ONLY: g1d_nomfich,g1d_unitfich,g1d_nvar,
     133     &  g1d_nomvar,g1d_titrevar,g1d_dimvar,g1d_nlayer,g1d_unitctl,
     134     &  g1d_nomctl,saveG1D
    131135      IMPLICIT NONE
    132136c.......................................................................
     
    142146c.......................................................................
    143147c
    144 #include "comg1d.h"
    145148
    146149
  • trunk/LMDZ.GENERIC/libf/phystd/wstats.F90

    r1315 r1397  
    33use mod_phys_lmdz_para, only : is_mpi_root, is_master, gather, klon_mpi_begin
    44use mod_grid_phy_lmdz, only : klon_glo, Grid1Dto2D_glo
     5use statto_mod, only: istats,istime,count
    56
    67implicit none
     
    910!#include "dimphys.h"
    1011#include "comconst.h"
    11 #include "statto.h"
    1212#include "netcdf.inc"
    1313
Note: See TracChangeset for help on using the changeset viewer.