Changeset 1226 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Apr 15, 2014, 11:46:48 PM (11 years ago)
Author:
aslmd
Message:

LMDZ.MARS : Replaced comcstfi and planete includes by modules.

Location:
trunk/LMDZ.MARS
Files:
2 added
2 deleted
63 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1225 r1226  
    20362036     Before, inifis has two very different tasks to do.
    203720373. a bit of cleaning as far as modules and saves are concerned
     2038
     2039== 15/04/2014 == AS
     2040Replaced comcstfi and planete includes by modules
  • trunk/LMDZ.MARS/libf/aeronomars/calchim.F90

    r1125 r1226  
    1515
    1616      use conc_mod, only: mmean ! mean molecular mass of the atmosphere
     17      USE comcstfi_h
    1718
    1819      implicit none
     
    7071#include "chimiedata.h"
    7172!#include "tracer.h"
    72 #include "comcstfi.h"
    7373#include "callkeys.h"
    7474!#include "conc.h"
  • trunk/LMDZ.MARS/libf/aeronomars/chemthermos.F90

    r1119 r1226  
    1010                            igcm_n2plus, igcm_hplus, igcm_hco2plus,     &
    1111                            igcm_elec, igcm_oplus
     12      USE comcstfi_h
    1213      IMPLICIT NONE
    1314!=======================================================================
     
    3132#include "dimensions.h"
    3233#include "dimphys.h"
    33 #include "comcstfi.h"
    3434#include "callkeys.h"
    3535!#include "comdiurn.h"
  • trunk/LMDZ.MARS/libf/aeronomars/concentrations.F

    r1047 r1226  
    1111     &                      igcm_hplus, igcm_hco2plus, mmol
    1212      use conc_mod, only: mmean, Akknew, rnew, cpnew
    13                          
     13      USE comcstfi_h                   
    1414      implicit none
    1515
     
    2929!#include "dimensions.h"
    3030!#include "dimphys.h"
    31 #include "comcstfi.h"
    3231#include "callkeys.h"
    3332!#include "comdiurn.h"
  • trunk/LMDZ.MARS/libf/aeronomars/conduction.F

    r1047 r1226  
    1919!#include "dimensions.h"
    2020!#include "dimphys.h"
    21 !#include "comcstfi.h"
    2221!#include "surfdat.h"
    2322!#include "chimiedata.h"
  • trunk/LMDZ.MARS/libf/aeronomars/deposition.F

    r1047 r1226  
    1414!#include "dimensions.h"
    1515!#include "dimphys.h"
    16 !#include "planete.h"
    1716!#include "chimiedata.h"
    1817!#include "conc.h"
  • trunk/LMDZ.MARS/libf/aeronomars/euvheat.F90

    r1119 r1226  
    3333!#include "dimensions.h"
    3434!#include "dimphys.h"
    35 !#include "comcstfi.h"
    3635#include "callkeys.h"
    3736!#include "comdiurn.h"
  • trunk/LMDZ.MARS/libf/aeronomars/moldiff.F

    r1047 r1226  
    88     &                      igcm_h2o_vap, mmol
    99      use conc_mod, only: rnew, mmean
     10      USE comcstfi_h
    1011      implicit none
    1112
    1213!#include "dimensions.h"
    1314!#include "dimphys.h"
    14 #include "comcstfi.h"
    1515!#include "callkeys.h"
    1616!#include "comdiurn.h"
  • trunk/LMDZ.MARS/libf/aeronomars/moldiff_red.F90

    r1047 r1226  
    33
    44use tracer_mod, only: noms, mmol
     5USE comcstfi_h
    56
    67implicit none
     
    89!#include "dimensions.h"
    910!#include "dimphys.h"
    10 #include "comcstfi.h"
    1111!#include "callkeys.h"
    1212!#include "comdiurn.h"
  • trunk/LMDZ.MARS/libf/aeronomars/molvis.F

    r1047 r1226  
    2222!#include "dimensions.h"
    2323!#include "dimphys.h"
    24 !#include "comcstfi.h"
    2524!#include "surfdat.h"
    2625!#include "chimiedata.h"
  • trunk/LMDZ.MARS/libf/aeronomars/perosat.F

    r1047 r1226  
    55      use tracer_mod, only: igcm_h2o2, mmol
    66      use conc_mod, only: mmean
     7      USE comcstfi_h
    78      IMPLICIT NONE
    89
     
    2627!#include "dimensions.h"
    2728!#include "dimphys.h"
    28 #include "comcstfi.h"
    2929!#include "chimiedata.h"
    3030!#include "tracer.h"
  • trunk/LMDZ.MARS/libf/aeronomars/photochemistry.F

    r1125 r1226  
    787787c*****************************************************************
    788788
     789      USE comcstfi_h
    789790      implicit none
    790791
     
    792793!#include "dimphys.h"
    793794#include "chimiedata.h"
    794 #include "comcstfi.h"
    795795
    796796cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     
    13621362c*****************************************************************
    13631363
     1364      USE comcstfi_h
    13641365      implicit none
    13651366
    13661367!#include "dimensions.h"
    13671368!#include "dimphys.h"
    1368 #include "comcstfi.h"
    13691369
    13701370cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
  • trunk/LMDZ.MARS/libf/aeronomars/surfacearea.F

    r1047 r1226  
    88     &                      igcm_ccn_number, varian, ccn_factor
    99      use conc_mod, only: rnew
     10      USE comcstfi_h
    1011      implicit none
    1112
     
    2021#include "dimensions.h"
    2122!#include "dimphys.h"
    22 #include "comcstfi.h"
    2323#include "callkeys.h"
    2424!#include "tracer.h"
  • trunk/LMDZ.MARS/libf/aeronomars/thermosphere.F

    r1047 r1226  
    66
    77      use conc_mod, only: rnew, cpnew
     8      USE comcstfi_h
    89      implicit none
    910
    1011!#include "dimensions.h"
    1112!#include "dimphys.h"
    12 #include "comcstfi.h"
    1313#include "callkeys.h"
    1414!#include "comdiurn.h"
  • trunk/LMDZ.MARS/libf/phymars/aeropacity.F

    r1224 r1226  
    1010      use comgeomfi_h, only: lati, sinlat ! grid point latitudes (rad)
    1111      use yomaer_h, only: tauvis
     12      use planete_h
     13      USE comcstfi_h
    1214       IMPLICIT NONE
    1315c=======================================================================
     
    5456!#include "dimphys.h"
    5557#include "callkeys.h"
    56 #include "comcstfi.h"
    5758!#include "comgeomfi.h"
    5859!#include "dimradmars.h"
     
    6162! naerkind is set in scatterers.h (built when compiling with makegcm -s #)
    6263#include"scatterers.h"
    63 #include "planete.h"
    6464#include "aerkind.h"
    6565
  • trunk/LMDZ.MARS/libf/phymars/callradite.F

    r1047 r1226  
    77      use dimradmars_mod, only: ndomainsz, nflev, nsun, nir
    88      use yomlw_h, only: gcp, nlaylte
     9      USE comcstfi_h
    910      IMPLICIT NONE
    1011c=======================================================================
     
    150151!#include "dimphys.h"
    151152!#include "dimradmars.h"
    152 #include "comcstfi.h"
    153153#include "callkeys.h"
    154154!#include "yomlw.h"
  • trunk/LMDZ.MARS/libf/phymars/callsedim.F

    r1047 r1226  
    1111     &                      igcm_ccn_mass, igcm_ccn_number,
    1212     &                      igcm_h2o_ice, nuice_sed, nuice_ref
     13      USE comcstfi_h
    1314      IMPLICIT NONE
    1415
     
    3132!#include "dimensions.h"
    3233!#include "dimphys.h"
    33 #include "comcstfi.h"
    3434!#include "tracer.h"
    3535#include "callkeys.h"
  • trunk/LMDZ.MARS/libf/phymars/calltherm_interface.F90

    r1212 r1226  
    4646      use comtherm_h
    4747      use tracer_mod, only: nqmx,noms
     48
     49      ! SHARED VARIABLES. This needs adaptations in another climate model.
     50      ! contains physical constant values such as
     51      ! "g" : gravitational acceleration (m.s-2)
     52      ! "r" : recuced gas constant (J.K-1.mol-1)
     53      ! "cpp" : specific heat of the atmosphere (J.kg-1.K-1)
     54      USE comcstfi_h
     55
    4856      implicit none
    49 
    50 ! SHARED VARIABLES. This needs adaptations in another climate model.
    51 #include "comcstfi.h" !contains physical constant values such as
    52                       ! "g" : gravitational acceleration (m.s-2)
    53                       ! "r" : recuced gas constant (J.K-1.mol-1)
    54                       ! "cpp" : specific heat of the atmosphere (J.kg-1.K-1)
    5557
    5658!--------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/co2snow.F

    r1130 r1226  
    44      use surfdat_h, only: iceradius, dtemisice
    55      use comgeomfi_h, only: lati ! grid point latitudes (rad)
     6      USE comcstfi_h
    67      IMPLICIT NONE
    78
     
    1819#include "dimensions.h"
    1920#include "dimphys.h"
    20 #include "comcstfi.h"
    2121!#include "surfdat.h"
    2222#include "callkeys.h"
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r1224 r1226  
    1       SUBROUTINE conf_phys(
    2      $           nq
    3      $           ,day_ini,pdaysec,ptimestep
    4      $           ,prad,pg,pr,pcpp
    5 #ifdef MESOSCALE
    6 #include "meso_inc/meso_inc_inifisinvar.F"
    7 #endif
    8      $           )
    9 !
     1      SUBROUTINE conf_phys(nq)
     2 
    103!=======================================================================
    114!
     
    4538! to use  'getin'
    4639      USE ioipsl_getincom, only : getin
    47       use tracer_mod, only : nqmx, nuice_sed, ccn_factor
     40      use tracer_mod, only : nuice_sed, ccn_factor
    4841      use surfdat_h, only: albedo_h2o_ice, inert_h2o_ice,
    4942     &                     frost_albedo_threshold
    5043      use yomaer_h,only: tauvis
    5144      use control_mod, only: ecritphy
    52 
    53 #ifdef MESOSCALE
    54       !! see meso_inc_inifisini.F
    55       use surfdat_h, only: emissiv,albedice,iceradius,
    56      &                     emisice,dtemisice,
    57      &                     z0_default,z0,
    58      &                     albedodat,phisfi,
    59      &                     zmea,zstd,zsig,zgam,zthe
    60       use slope_mod, only: theta_sl,psi_sl
    61       use comsoil_h, only: volcapa !!MESOSCALE -- needed to fill volcapa
    62 #endif
     45      use planete_h
     46      USE comcstfi_h, only: daysec,dtphys
    6347
    6448      IMPLICIT NONE
    6549#include "dimensions.h"
    6650#include "dimphys.h"
    67 #include "planete.h"
    68 #include "comcstfi.h"
    6951!#include "comsaison.h"
    7052!#include "comdiurn.h"
     
    8163#include"scatterers.h"
    8264
    83 #ifdef MESOSCALE
    84 #include "meso_inc/meso_inc_inifisvar.F"
    85 #endif
    86       REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec
    87 
    88       REAL,INTENT(IN) :: ptimestep
    89       INTEGER,INTENT(IN) :: nq,day_ini
     65      INTEGER,INTENT(IN) :: nq
    9066      INTEGER ig,ierr
    9167 
    9268      CHARACTER ch1*12
    9369      CHARACTER ch80*80
    94 
    95 !      logical chem, h2o
    96 
    97 !      chem = .false.
    98 !      h2o = .false.
    99 
    100 
    101       pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
    102 
    103       rad=prad
    104       cpp=pcpp
    105       g=pg
    106       r=pr
    107       rcp=r/cpp
    108       daysec=pdaysec
    109       dtphys=ptimestep
    110 
    111       nqmx=nq
    112 
    113 !! MESOSCALE INITIALIZATIONS
    114 #ifdef MESOSCALE
    115 #include "meso_inc/meso_inc_inifisini.F"
    116 #endif
    11770
    11871      ! read in 'ecritphy' (frequency of calls to physics, in dynamical steps)
  • trunk/LMDZ.MARS/libf/phymars/convadj.F

    r1047 r1226  
    88      use tracer_mod, only: noms, ! tracer names
    99     &                      igcm_h2o_vap ! index of water vapor tracer
     10      USE comcstfi_h
    1011      implicit none
    1112
     
    3334!#include "dimensions.h"
    3435!#include "dimphys.h"
    35 #include "comcstfi.h"
    3636#include "callkeys.h"
    3737!#include "tracer.h"
  • trunk/LMDZ.MARS/libf/phymars/drag_noro.F

    r1047 r1226  
    5252c
    5353      use dimradmars_mod, only:  ndlo2
     54      USE comcstfi_h
    5455      IMPLICIT none
    5556c======================================================================
     
    7374!#include "dimphys.h"
    7475!#include "dimradmars.h"
    75 #include "comcstfi.h"
    7676c
    7777c ARGUMENTS
  • trunk/LMDZ.MARS/libf/phymars/dustdevil.F

    r1047 r1226  
    44      use tracer_mod, only: alpha_devil
    55      use surfdat_h, only: z0_default
     6      USE comcstfi_h
    67      IMPLICIT NONE
    78
     
    3132!#include "dimensions.h"
    3233!#include "dimphys.h"
    33 #include "comcstfi.h"     
    3434c#include "comconst.h"        ! TEMPORAIRE AVEC ANLDEVIL !!!!
    3535!#include "surfdat.h"
  • trunk/LMDZ.MARS/libf/phymars/dustlift.F

    r1047 r1226  
    1010     &                      ref_r0,r3n_q
    1111#endif
     12      USE comcstfi_h
    1213      IMPLICIT NONE
    1314
     
    2627!#include "dimensions.h"
    2728!#include "dimphys.h"
    28 #include "comcstfi.h"
    2929!#include "tracer.h"
    3030
  • trunk/LMDZ.MARS/libf/phymars/eofdump_mod.F90

    r1130 r1226  
    8080
    8181      use comgeomfi_h, only: long, lati
     82      use comcstfi_h
    8283      implicit none
    8384!
     
    8788!#include "dimphys.h"
    8889#include "comvert.h"
    89 #include "comcstfi.h"
    9090!#include "comgeomfi.h"
    9191
  • trunk/LMDZ.MARS/libf/phymars/getslopes.F90

    r1047 r1226  
    33use comgeomfi_h, only: long, lati
    44use slope_mod, only: theta_sl, psi_sl
     5USE comcstfi_h
    56implicit none
    67
     
    910!#include "slope.h"
    1011!#include "comgeomfi.h"
    11 #include "comcstfi.h"
    1212
    1313
  • trunk/LMDZ.MARS/libf/phymars/growthrate.F

    r1036 r1226  
    22
    33      use tracer_mod, only: rho_ice
     4      USE comcstfi_h
    45      IMPLICIT NONE
    56
     
    2122#include "dimensions.h"
    2223#include "dimphys.h"
    23 #include "comcstfi.h"
    2424!#include "tracer.h"
    2525#include "microphys.h"
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds.F

    r1212 r1226  
    1111     &                      igcm_ccn_number
    1212      use conc_mod, only: mmean
     13      USE comcstfi_h
    1314      implicit none
    1415     
     
    3637!#include "dimensions.h"
    3738!#include "dimphys.h"
    38 #include "comcstfi.h"
    3939#include "callkeys.h"
    4040!#include "tracer.h"
  • trunk/LMDZ.MARS/libf/phymars/iniorbit.F

    r38 r1226  
    11      SUBROUTINE iniorbit
    22     $     (paphelie,pperiheli,pyear_day,pperi_day,pobliq)
     3      use planete_h
     4      USE comcstfi_h
    35      IMPLICIT NONE
    46
     
    3436c   Declarations:
    3537c   -------------
    36 
    37 #include "planete.h"
    38 #include "comcstfi.h"
    3938
    4039c   Arguments:
  • trunk/LMDZ.MARS/libf/phymars/iniphysiq.F90

    r1224 r1226  
    6969! copy some fundamental parameters to physics
    7070! and do some initializations
    71 call phys_state_var_init(klon_omp,nlayer,nqtot,rlatd,rlond,airephy)
    72 call conf_phys(nqtot,pdayref,punjours,ptimestep,prad,pg,pr,pcpp)
     71call phys_state_var_init(klon_omp,nlayer,nqtot, &
     72                         rlatd,rlond,airephy, &
     73                         punjours,ptimestep,prad,pg,pr,pcpp)
     74call conf_phys(nqtot)
    7375
    7476!$OMP END PARALLEL
  • trunk/LMDZ.MARS/libf/phymars/initracer.F

    r1224 r1226  
    55#endif
    66       use tracer_mod
     7       USE comcstfi_h
    78       IMPLICIT NONE
    89c=======================================================================
     
    2829!#include "dimensions.h"
    2930!#include "dimphys.h"
    30 #include "comcstfi.h"
    3131#include "callkeys.h"
    3232!#include "tracer.h"
  • trunk/LMDZ.MARS/libf/phymars/iniwrite.F

    r1047 r1226  
    22
    33      use comsoil_h, only: mlayer, nsoilmx
     4      USE comcstfi_h
    45      IMPLICIT NONE
    56
     
    2324#include "paramet.h"
    2425!include "comconst.h"
    25 #include "comcstfi.h"
    2626#include "comvert.h"
    2727#include "comgeom.h"
  • trunk/LMDZ.MARS/libf/phymars/iniwritesoil.F90

    r1047 r1226  
    66
    77use comsoil_h, only: mlayer, inertiedat, nsoilmx
     8USE comcstfi_h
    89
    910implicit none
     
    1213!#include"dimphys.h"
    1314#include"paramet.h"
    14 #include"comcstfi.h"
    1515#include"comgeom.h"
    1616!#include"comsoil.h"
  • trunk/LMDZ.MARS/libf/phymars/lect_start_archive.F

    r1223 r1226  
    1919      use infotrac, only: tname
    2020      use comsoil_h, only: nsoilmx, layer, mlayer, volcapa, inertiedat
     21      use planete_h
    2122      implicit none
    2223
     
    2728!#include "dimradmars.h"
    2829!#include "yomaer.h"
    29 #include "planete.h"
    3030#include "paramet.h"
    3131#include "comconst.h"
  • trunk/LMDZ.MARS/libf/phymars/lwdiff.F

    r1047 r1226  
    77     &                          ndlo2
    88      use yomlw_h, only: nlaylte
     9      USE comcstfi_h
    910      IMPLICIT NONE
    1011 
     
    1314!#include "dimradmars.h"
    1415#include "callkeys.h"
    15 #include "comcstfi.h"
    1616
    1717!#include "yomaer.h"
  • trunk/LMDZ.MARS/libf/phymars/lwi.F

    r1047 r1226  
    66      use dimradmars_mod, only: ndlo2, ndlon, nflev, nir
    77      use yomlw_h, only: gcp, nlaylte, xi
     8      USE comcstfi_h
    89      implicit none
    910
     
    1415#include "comg1d.h"
    1516#include "callkeys.h"
    16 #include "comcstfi.h"
    1717!#include "yomlw.h"
    1818 
  • trunk/LMDZ.MARS/libf/phymars/lwu.F

    r1047 r1226  
    3333      use dimradmars_mod, only: ndlo2, nir, nuco2, ndlon, nflev
    3434      use yomlw_h, only: nlaylte, tref, at, bt, cst_voigt
     35      USE comcstfi_h
    3536      implicit none
    3637
     
    3839!#include "dimphys.h"
    3940!#include "dimradmars.h"
    40 #include "comcstfi.h"
    4141
    4242!#include "yomaer.h"
  • trunk/LMDZ.MARS/libf/phymars/newcondens.F

    r1224 r1226  
    99       use surfdat_h, only: emissiv, phisfi
    1010       use comgeomfi_h, only: lati ! grid point latitudes (rad)
     11       use planete_h
     12       USE comcstfi_h
    1113       IMPLICIT NONE
    1214c=======================================================================
     
    5860#include "dimensions.h"
    5961!#include "dimphys.h"
    60 #include "comcstfi.h"
    6162!#include "surfdat.h"
    6263!#include "comgeomfi.h"
     
    6566#include "callkeys.h"
    6667!#include "tracer.h"
    67 #include "planete.h"
    6868
    6969c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/newsedim.F

    r1047 r1226  
    11      SUBROUTINE newsedim(ngrid,nlay,naersize,nrhosize,ptimestep,
    22     &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq,beta)
     3      USE comcstfi_h
    34      IMPLICIT NONE
    45
     
    1617!#include "dimensions.h"
    1718!#include "dimphys.h"
    18 #include "comcstfi.h"
     19
    1920c
    2021c   arguments:
  • trunk/LMDZ.MARS/libf/phymars/newstart.F

    r1224 r1226  
    2828      use iostart, only: open_startphy
    2929      use comgeomphy, only: initcomgeomphy
     30      use planete_h
    3031      implicit none
    3132
     
    3738!#include "dimradmars.h"
    3839!#include "yomaer.h"
    39 #include "planete.h"
    4040#include "paramet.h"
    4141#include "comconst.h"
     
    383383!    (for instance initracer needs to know about some flags, and/or
    384384!      'datafile' path may be changed by user)
    385       call phys_state_var_init(ngridmx,llm,nqtot,latfi,lonfi,airefi)
    386       call conf_phys(nqtot,day_ini,daysec,dtphys,rad,g,r,cpp)
     385      call phys_state_var_init(ngridmx,llm,nqtot,
     386     .                         latfi,lonfi,airefi,
     387     .                         daysec,dtphys,rad,g,r,cpp)
     388      call conf_phys(nqtot)
    387389
    388390c=======================================================================
  • trunk/LMDZ.MARS/libf/phymars/nirco2abs.F

    r1224 r1226  
    44       use tracer_mod, only: igcm_co2, igcm_o
    55       use comgeomfi_h, only: sinlon, coslon, sinlat, coslat
     6       USE comcstfi_h
    67       IMPLICIT NONE
    78c=======================================================================
     
    4849!#include "dimensions.h"
    4950!#include "dimphys.h"
    50 #include "comcstfi.h"
    5151#include "callkeys.h"
    5252!#include "comdiurn.h"
  • trunk/LMDZ.MARS/libf/phymars/nlte_tcool.F

    r1124 r1226  
    13601360      function hrkday_convert                       
    13611361     @     ( mmean_nlte,cpmean_nlte )         
    1362      
     1362      USE comcstfi_h
    13631363      implicit none                           
    13641364     
    1365       include 'comcstfi.h'
    13661365      include 'param.h'
    13671366     
  • trunk/LMDZ.MARS/libf/phymars/nuclea.F

    r1036 r1226  
    22*                                                     *
    33      subroutine nuclea(ph2o,temp,sat,n_ccn,nucrate)
     4      USE comcstfi_h
    45      implicit none
    56*                                                     *
     
    1617#include "dimensions.h"
    1718#include "dimphys.h"
    18 #include "comcstfi.h"
    1919!#include "tracer.h"
    2020#include "microphys.h"
  • trunk/LMDZ.MARS/libf/phymars/orbite.F

    r38 r1226  
    11      SUBROUTINE orbite(pls,pdist_sol,pdecli)
     2      use planete_h
     3      USE comcstfi_h
    24      IMPLICIT NONE
    35
     
    3234c   -------------
    3335
    34 #include "planete.h"
    35 #include "comcstfi.h"
    36 
    3736c arguments:
    3837c ----------
  • trunk/LMDZ.MARS/libf/phymars/orodrag.F

    r1047 r1226  
    7272C-----------------------------------------------------------------------
    7373      use dimradmars_mod, only: ndlo2
     74      USE comcstfi_h
    7475      implicit none
    7576C
     
    8283      integer, save :: kfdia ! =NDLO2
    8384
    84 #include "comcstfi.h"
    8585#include "yoegwd.h"
    8686C-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/orosetup.F

    r1047 r1226  
    4747C-----------------------------------------------------------------------
    4848      use dimradmars_mod, only: ndlo2
     49      USE comcstfi_h
    4950      implicit none
    5051C
     
    5556      integer klon,klev,kidia,kfdia
    5657
    57 #include "comcstfi.h"
    5858#include "yoegwd.h"
    5959
  • trunk/LMDZ.MARS/libf/phymars/pbl_parameters.F

    r1212 r1226  
    22     & pg,zzlay,zzlev,pu,pv,wstar_in,hfmax,zmax,pts,ph,z_out,n_out,
    33     & T_out,u_out,ustar,tstar,L_mo,vhf,vvv)
     4      USE comcstfi_h
    45      IMPLICIT NONE
    56!=======================================================================
     
    4950!   -------------
    5051
    51 #include "comcstfi.h"
    5252#include "callkeys.h"
    5353
  • trunk/LMDZ.MARS/libf/phymars/phyetat0.F90

    r1208 r1226  
    1010                     get_field, get_var, inquire_field, &
    1111                     inquire_dimension, inquire_dimension_length
     12  use planete_h 
     13  use comcstfi_h
     14
    1215  implicit none
    1316!======================================================================
     
    2629!#include "comgeomfi.h"
    2730!#include "surfdat.h"
    28 #include "planete.h"
    2931!#include "dimradmars.h"
    3032!#include "yomaer.h"
    31 #include "comcstfi.h"
    3233!#include "tracer.h"
    3334!#include "advtrac.h"
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r1221 r1226  
    2222                      put_var, put_field, length
    2323  use mod_grid_phy_lmdz, only : klon_glo
     24  use planete_h
     25  use comcstfi_h
    2426
    2527  implicit none
    26 #include "planete.h"
    27 #include "comcstfi.h"
    2828 
    2929  character(len=*), intent(in) :: filename
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init.F

    r1224 r1226  
    1       SUBROUTINE phys_state_var_init(ngrid,nlayer,nq,plat,plon,parea)
     1      SUBROUTINE phys_state_var_init(ngrid
     2     .               ,nlayer,nq,plat,plon,parea
     3     .               ,pdaysec,ptimestep,prad,pg,pr,pcpp)
    24
    35!=======================================================================
     
    810!   Allocate arrays in modules
    911!   Fill geometrical arrays
     12!   Fill a first set of physical constants
    1013!   -- was done previously in inifis
    1114!
     
    3033      use comsaison_h, only: ini_comsaison_h
    3134      use surfdat_h, only: ini_surfdat_h
    32       use comgeomfi_h, only: ini_comgeomfi_h,long,lati,area,totarea,ini_sincosgeom
     35      use comgeomfi_h, only: ini_comgeomfi_h
     36     .                       ,long,lati,area,totarea
     37     .                       ,ini_sincosgeom
    3338      use comsoil_h, only: ini_comsoil_h
    3439      use dimradmars_mod, only: ini_dimradmars_mod
     
    3742      use conc_mod, only: ini_conc_mod
    3843      use turb_mod, only: ini_turb_mod
     44      use comcstfi_h, only: pi,rad,cpp,g,r,rcp,daysec,dtphys
     45      use tracer_mod, only: nqmx
    3946
    4047      IMPLICIT NONE
     
    4249      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
    4350      REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
     51      REAL,INTENT(IN) :: pdaysec,ptimestep,prad,pg,pr,pcpp
    4452      EXTERNAL SSUM
    4553      REAL SSUM
     54
     55      ! set dimension in tracer_mod
     56      nqmx=nq
     57
     58      ! set parameters in comcstfi_h
     59      pi=2.*asin(1.)
     60      rad=prad
     61      cpp=pcpp
     62      g=pg
     63      r=pr
     64      rcp=r/cpp
     65      daysec=pdaysec
     66      dtphys=ptimestep
    4667
    4768      ! allocate "slope_mod" arrays
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r1224 r1226  
    3333     &                          dtrad, fluxrad_sky, fluxrad, albedo
    3434      use turb_mod, only: q2, wstar, hfmax_th
     35      use planete_h
     36      USE comcstfi_h
    3537#ifdef MESOSCALE
    3638      use comsoil_h, only: mlayer,layer
     
    148150!#include "comdiurn.h"
    149151#include "callkeys.h"
    150 #include "comcstfi.h"
    151 #include "planete.h"
    152152!#include "comsaison.h"
    153153!#include "control.h"
  • trunk/LMDZ.MARS/libf/phymars/simpleclouds.F

    r1047 r1226  
    55      USE updaterad
    66      use tracer_mod, only: igcm_h2o_vap, igcm_h2o_ice
     7      USE comcstfi_h
    78      implicit none
    89c------------------------------------------------------------------
     
    3132!#include "dimensions.h"
    3233!#include "dimphys.h"
    33 #include "comcstfi.h"
    3434#include "callkeys.h"
    3535!#include "tracer.h"
  • trunk/LMDZ.MARS/libf/phymars/solarlong.F

    r608 r1226  
    11      SUBROUTINE solarlong(pday,psollong)
     2      use planete_h
     3      USE comcstfi_h
    24      IMPLICIT NONE
    35
     
    4042c   Declarations:
    4143c   -------------
    42 
    43 #include "planete.h"
    44 #include "comcstfi.h"
    4544
    4645c arguments:
  • trunk/LMDZ.MARS/libf/phymars/surfini.F

    r1224 r1226  
    1212      use mod_phys_lmdz_para, only : is_master, gather, scatter
    1313#endif
     14      USE comcstfi_h
    1415      IMPLICIT NONE
    1516c=======================================================================
     
    2728!#include "tracer.h"
    2829!#include "comgeomfi.h"
    29 #include "comcstfi.h"
    3030
    3131#include "datafile.h"
  • trunk/LMDZ.MARS/libf/phymars/swrayleigh.F

    r38 r1226  
    11      SUBROUTINE swrayleigh(kdlon,knu,ppsol,prmu,prayl)
    2                                                   
     2       USE comcstfi_h                                                  
    33       IMPLICIT NONE
    44c=======================================================================
     
    2323c
    2424c=======================================================================
    25 #include "comcstfi.h"
    2625
    2726c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/tabfi.F

    r1130 r1226  
    5050      use iostart, only: get_var
    5151      use mod_phys_lmdz_para, only: is_parallel
     52      use comcstfi_h
     53      use planete_h
    5254      implicit none
    5355 
    5456!#include "dimensions.h"
    5557!#include "dimphys.h"
    56 #include "comcstfi.h"
    5758!#include "comgeomfi.h"
    58 #include "planete.h"
    5959!#include "surfdat.h"
    6060!#include "comsoil.h"
  • trunk/LMDZ.MARS/libf/phymars/testphys1d.F

    r1224 r1226  
    1515      use phyredem, only: physdem0,physdem1
    1616      use comgeomphy, only: initcomgeomphy
     17      use planete_h
     18      use comcstfi_h
    1719      IMPLICIT NONE
    1820
     
    4648!#include "comdiurn.h"
    4749#include "callkeys.h"
    48 #include "comcstfi.h"
    49 #include "planete.h"
    5050!#include "comsaison.h"
    5151!#include "yomaer.h"
     
    476476!  and allocates some arrays
    477477!Mars possible matter with dtphys in input and include!!!
    478       call phys_state_var_init(1,llm,nq,latitude,longitude,1.0)
    479       call conf_phys(nq,day0,daysec,dtphys,rad,g,r,cpp)
     478      call phys_state_var_init(1,llm,nq,
     479     .          latitude,longitude,1.0,
     480     .          daysec,dtphys,rad,g,r,cpp)
     481      call conf_phys(nq)
    480482
    481483
  • trunk/LMDZ.MARS/libf/phymars/thermcell_main_mars.F90

    r1212 r1226  
    4646      use planetwide_mod, only: planetwide_maxval
    4747#endif
     48      ! SHARED VARIABLES. This needs adaptations in another climate model.
     49      ! contains physical constant values such as
     50      ! "g" : gravitational acceleration (m.s-2)
     51      ! "r" : recuced gas constant (J.K-1.mol-1)
     52      USE comcstfi_h
    4853
    4954      IMPLICIT NONE
    5055
    5156!=======================================================================
    52 
    53 ! SHARED VARIABLES. This needs adaptations in another climate model.
    54 #include "comcstfi.h" !contains physical constant values such as
    55                       ! "g" : gravitational acceleration (m.s-2)
    56                       ! "r" : recuced gas constant (J.K-1.mol-1)
    5757
    5858! ============== INPUTS ==============
  • trunk/LMDZ.MARS/libf/phymars/updaterad.F90

    r1036 r1226  
    6363subroutine updaterice_micro(qice,qccn,nccn,coeff,rice,rhocloud)
    6464use tracer_mod, only: rho_dust, rho_ice
    65 implicit none
    66 
    67 #include "dimensions.h"
    68 #include "dimphys.h"
    69 #include "comcstfi.h"
     65USE comcstfi_h
     66implicit none
     67
     68#include "dimensions.h"
     69#include "dimphys.h"
    7070!#include "tracer.h"
    7171
     
    120120subroutine updaterice_typ(qice,tau,pzlay,rice)
    121121use tracer_mod, only: rho_ice
    122 implicit none
    123 
    124 #include "dimensions.h"
    125 #include "dimphys.h"
    126 #include "comcstfi.h"
     122USE comcstfi_h
     123implicit none
     124
     125#include "dimensions.h"
     126#include "dimphys.h"
    127127!#include "tracer.h"
    128128
     
    178178subroutine updaterdust(qdust,ndust,rdust,tauscaling)
    179179use tracer_mod, only: r3n_q
    180 implicit none
    181 
    182 #include "dimensions.h"
    183 #include "dimphys.h"
    184 #include "comcstfi.h"
     180USE comcstfi_h
     181implicit none
     182
     183#include "dimensions.h"
     184#include "dimphys.h"
    185185!#include "tracer.h"
    186186
     
    234234subroutine updaterccn(qccn,nccn,rccn,tauscaling)
    235235use tracer_mod, only: rho_dust
    236 implicit none
    237 
    238 #include "dimensions.h"
    239 #include "dimphys.h"
    240 #include "comcstfi.h"
     236USE comcstfi_h
     237implicit none
     238
     239#include "dimensions.h"
     240#include "dimphys.h"
    241241!#include "tracer.h"
    242242
  • trunk/LMDZ.MARS/libf/phymars/updatereffrad.F

    r1224 r1226  
    99     &                       ref_r0, igcm_dust_submicron
    1010       USE dimradmars_mod, only: nueffdust
     11       USE comcstfi_h
    1112       IMPLICIT NONE
    1213c=======================================================================
     
    3334!#include "dimensions.h"
    3435!#include "dimphys.h"
    35 #include "comcstfi.h"
    3636#include "callkeys.h"
    3737!#include "dimradmars.h"
  • trunk/LMDZ.MARS/libf/phymars/vdif_cd.F

    r765 r1226  
    55#endif
    66     &                  )
     7      USE comcstfi_h
    78      IMPLICIT NONE
    89c=======================================================================
     
    3940c   -------------
    4041
    41 #include "comcstfi.h"
    4242#include "callkeys.h"
    4343
  • trunk/LMDZ.MARS/libf/phymars/vdifc.F

    r1224 r1226  
    1515     &                      igcm_h2o_ice, alpha_lift
    1616      use surfdat_h, only: watercaptag, frost_albedo_threshold, dryness
     17      USE comcstfi_h
    1718      IMPLICIT NONE
    1819
     
    3940!#include "dimensions.h"
    4041!#include "dimphys.h"
    41 #include "comcstfi.h"
    4242#include "callkeys.h"
    4343!#include "surfdat.h"
  • trunk/LMDZ.MARS/libf/phymars/watercloud.F

    r1047 r1226  
    77      USE ioipsl_getincom
    88      USE updaterad
     9      USE comcstfi_h
    910      use tracer_mod, only: nqmx, igcm_h2o_vap, igcm_h2o_ice,
    1011     &                      igcm_dust_mass, igcm_dust_number,
     
    3637!#include "dimensions.h"
    3738!#include "dimphys.h"
    38 #include "comcstfi.h"
    3939#include "callkeys.h"
    4040!#include "tracer.h"
  • trunk/LMDZ.MARS/libf/phymars/writeg1d.F

    r141 r1226  
    124124
    125125      SUBROUTINE endg1d(ngrid,nlayer,zlayer,ndt)
     126      USE comcstfi_h
    126127      IMPLICIT NONE
    127128c.......................................................................
     
    138139c
    139140#include "comg1d.h"
    140 #include "comcstfi.h"
    141141c
    142142c.......................................................................
Note: See TracChangeset for help on using the changeset viewer.