Changeset 3726 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Apr 17, 2025, 9:45:14 AM (2 months ago)
Author:
emillour
Message:

Mars PCM:
Turn "callkeys.h" into module "callkeys_mod.F90"
EM

Location:
trunk/LMDZ.MARS
Files:
67 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3715 r3726  
    47954795Fix for the 1D following the reindexing in restartfi files: the "ind_cell_glo"
    47964796array must also be allocated and filled at initialization.
     4797
     4798== 17/04/2025 == EM
     4799Turn "callkeys.h" into module "callkeys_mod.F90"
  • trunk/LMDZ.MARS/libf/aeronomars/calchim_mod.F90

    r3466 r3726  
    4040      use iono_h, only: temp_elect
    4141      use wstats_mod, only: wstats
     42      use callkeys_mod, only: photochem
    4243
    4344      implicit none
     
    8081!
    8182!=======================================================================
    82 
    83 include "callkeys.h"
    8483
    8584!     input:
  • trunk/LMDZ.MARS/libf/aeronomars/chemthermos.F90

    r3464 r3726  
    4040!    ------------------
    4141!
    42       include "callkeys.h"
     42
    4343!-----------------------------------------------------------------------
    4444!    Input/Output
  • trunk/LMDZ.MARS/libf/aeronomars/euvheat.F90

    r3464 r3726  
    1414      use conc_mod, only: rnew, cpnew
    1515      use hrtherm_mod, only: hrtherm
     16      use callkeys_mod, only: euveff
    1617      IMPLICIT NONE
    1718!=======================================================================
     
    3839!    ------------------
    3940!
    40       include "callkeys.h"
     41
    4142!-----------------------------------------------------------------------
    4243!    Input/Output
  • trunk/LMDZ.MARS/libf/aeronomars/hrtherm.F

    r3464 r3726  
    2020
    2121      implicit none
    22 
    23 c     common variables and constants
    24       include "callkeys.h"
    25 
    2622
    2723c    local parameters and variables
  • trunk/LMDZ.MARS/libf/aeronomars/inichim_newstart.F90

    r3466 r3726  
    1414      use dust_param_mod, only: doubleq, submicron, dustbin
    1515      use intrplf_mod, only: intrplf
     16      use callkeys_mod, only: microphys, rdstorm, topflows
     17      use callkeys_mod, only: co2clouds, co2useh2o, meteo_flux
    1618      implicit none
    1719
     
    4446!=======================================================================
    4547
    46       include "callkeys.h"
    4748
    4849! inputs :
  • trunk/LMDZ.MARS/libf/aeronomars/jthermcalc_e107.F

    r3464 r3726  
    2626      use comsaison_h, only: dist_sol
    2727      use jthermcalc_util, only: column, interfast
     28      use callkeys_mod, only: solvarmod, fixed_euv_value
    2829
    2930      implicit none
    30 
    31       include "callkeys.h"
    3231
    3332c     input and output variables
  • trunk/LMDZ.MARS/libf/aeronomars/jthermcalc_util.F

    r3464 r3726  
    2323
    2424      implicit none
    25 
    26 
    27 c     common variables and constants
    28       include 'callkeys.h'
    29 
    3025
    3126
     
    719714      use param_v4_h, only: ninter,
    720715     .                      fluxtop, ct1, ct2, p1, p2
     716      use callkeys_mod, only: solvarmod
    721717      implicit none
    722718
    723719
    724 !     common variables and constants
    725       include "callkeys.h"
    726 
    727 
    728720!     Arguments
    729721
    730       real date
     722      real,intent(inout) :: date
    731723
    732724
  • trunk/LMDZ.MARS/libf/aeronomars/moldiffcoeff.F

    r3466 r3726  
    2222c
    2323c=======================================================================
    24 #include "callkeys.h"
    2524
    2625c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/aeronomars/moldiffcoeff_red.F

    r3015 r3726  
    1818c
    1919c=======================================================================
    20       include "callkeys.h"
    2120
    2221c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/aeronomars/param_read_e107.F

    r3466 r3726  
    2525      USE mod_phys_lmdz_para, ONLY: is_master
    2626      USE mod_phys_lmdz_transfert_para, ONLY: bcast
     27      use callkeys_mod, only: solvaryear
    2728
    2829      implicit none
    2930
    3031
    31 c     common variables and constants
    32       include "callkeys.h"
    33  
    34  
    3532c     local variables
    3633
  • trunk/LMDZ.MARS/libf/aeronomars/paramfoto_compact.F

    r3464 r3726  
    20172017
    20182018      implicit none
    2019 
    2020       include 'callkeys.h'
    20212019
    20222020c     arguments
  • trunk/LMDZ.MARS/libf/aeronomars/photochemistry.F90

    r3466 r3726  
    3535
    3636implicit none
    37 
    38 include "callkeys.h"
    3937
    4038!===================================================================
     
    39473945     &                      igcm_hdo_vap, igcm_od, igcm_d, igcm_hd,      &
    39483946     &                      igcm_do2, igcm_hdo2
    3949 
    39503947      implicit none
    3951 
    3952       include "callkeys.h"
    39533948
    39543949!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     
    42554250      implicit none
    42564251
    4257 #include "callkeys.h"
    4258 
    42594252!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    42604253!     inputs:
  • trunk/LMDZ.MARS/libf/aeronomars/surfacearea.F

    r3466 r3726  
    1616      use comcstfi_h, only: pi
    1717      use wstats_mod, only: wstats
     18      use callkeys_mod, only: microphys
    1819      implicit none
    1920
     
    2526!     version 1.2 april 2012
    2627!==========================================================================
    27 
    28       include "callkeys.h"
    2928
    3029! input
  • trunk/LMDZ.MARS/libf/aeronomars/thermosphere.F

    r3710 r3726  
    2424      USE comcstfi_h, only: r, cpp
    2525      use mod_phys_lmdz_para, only : is_master
     26      use callkeys_mod, only: calleuv, callconduct, callmoldiff
     27      use callkeys_mod, only: callmolvis
    2628      implicit none
    27 
    28       include "callkeys.h"
    2929
    3030      integer,intent(in) :: ngrid ! number of atmospheric columns
  • trunk/LMDZ.MARS/libf/phymars/aeropacity_mod.F

    r3125 r3726  
    4141      use surfdat_h,only: alpha_hmons,contains_mons
    4242      use read_dust_scenario_mod, only: read_dust_scenario
     43      use callkeys_mod, only: co2clouds, activeco2ice,
     44     &                        water, activice, CLFvarying,
     45     &                        CLFvaryingCO2, iaervar,
     46     &                        rdstorm, topflows
    4347     
    4448       IMPLICIT NONE
     
    6064c   
    6165c=======================================================================
    62       include "callkeys.h"
    6366
    6467c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/aeroptproperties.F

    r2932 r3726  
    99     &                omegaREFvis, omegaREFir
    1010      use write_output_mod, only: write_output
     11
    1112      IMPLICIT NONE
    1213c     =============================================================
     
    2728c     Authors: J.-B. Madeleine, F. Forget, F. Montmessin
    2829c     =============================================================
    29 
    30       include "callkeys.h"
    3130
    3231c     Local variables
  • trunk/LMDZ.MARS/libf/phymars/albedocaps.F90

    r3586 r3726  
    1313
    1414implicit none
    15 
    16 include"callkeys.h"
    1715
    1816! arguments:
  • trunk/LMDZ.MARS/libf/phymars/callkeys_mod.F90

    r3725 r3726  
    1 !
    2 ! For Fortran 77/Fortran 90 compliance always use line continuation
    3 ! symbols '&' in columns 73 and 6
    4 !
    5 ! NB: to keep commons aligned, it is better to split them in groups
    6 !     of given types (logical, integer, real, ...)
     1MODULE callkeys_mod
    72
    8       COMMON/callkeys_l/callrad,calldifv,calladj,callcond,callsoil      &
    9      &   ,season,diurnal,calllott,calleofdump                           &
    10      &   ,callnirco2,callnlte,callthermos,callconduct,calleuv           &
    11      &   ,callmolvis,callmoldiff,thermochem,thermoswater,callemis       &
    12      &   ,callg2d,linear,rayleigh                                       &
    13      &   ,scavenging,sedimentation                                      &
    14      &   ,activice,water,microphys,supersat,caps,photochem              &
    15      &   ,calltherm,callrichsl,callslope,tituscap,callyamada4,co2clouds &
    16      &   ,co2useh2o,meteo_flux,activeco2ice,CLFvaryingCO2,spantCO2      &
    17      &   ,CLFvarying,satindexco2,rdstorm,topflows,calllott_nonoro       &
    18      &   ,latentheat_surfwater,gwd_convective_source,startphy_file      &
    19      &   ,hdo,hdofrac,cst_cap_albedo,temp_dependent_m,refill_watercap   &
    20      &   ,cloud_adapt_ts,callatke,surfaceice_tifeedback                 &
    21      &   , poreice_tifeedback
    22 !$OMP THREADPRIVATE(/callkeys_l/)
     3IMPLICIT NONE
    234
    24      
    25       COMMON/callkeys_i/iradia,iaervar,ilwd,ilwb,ilwn,ncouche           &
    26      &   ,nltemodel,nircorr,solvarmod,solvaryear,dustinjection
    27 !$OMP THREADPRIVATE(/callkeys_i/)
    28      
    29       COMMON/callkeys_r/semi,alphan,euveff,                             &
    30      &   tke_heat_flux,dustrefir,fixed_euv_value,CLFfixval,             &
    31      &   coeff_injection,ti_injection,tf_injection,coeff_detrainment
    32 !$OMP THREADPRIVATE(/callkeys_r/)
    33      
    34       LOGICAL callrad,calldifv,calladj,callcond,callsoil,               &
    35      &   season,diurnal,calllott,calllott_nonoro                        &
    36      &   ,calleofdump                                                   &
    37      &   ,callnirco2,callnlte,callthermos,callconduct,                  &
    38      &    calleuv,callmolvis,callmoldiff,thermochem,thermoswater        &
    39      &   ,calltherm,callrichsl,callslope,tituscap,callyamada4,callatke
     5logical,save :: startphy_file
     6!$OMP THREADPRIVATE(startphy_file)
    407
    41       COMMON/aeroutput/dustiropacity
    42 !$OMP THREADPRIVATE(/aeroutput/)
     8logical,save :: callrad,calldifv,calladj,callcond,callsoil
     9!$OMP THREADPRIVATE(callrad,calldifv,calladj,callcond,callsoil)
     10logical,save :: season,diurnal,calllott,calllott_nonoro
     11!$OMP THREADPRIVATE(season,diurnal,calllott,calllott_nonoro)
     12logical,save :: calleofdump
     13!$OMP THREADPRIVATE(calleofdump)
     14logical,save :: callnirco2,callnlte,callthermos,callconduct
     15!$OMP THREADPRIVATE(callnirco2,callnlte,callthermos,callconduct)
     16logical,save :: calleuv,callmolvis,callmoldiff,thermochem,thermoswater
     17!$OMP THREADPRIVATE(calleuv,callmolvis,callmoldiff,thermochem,thermoswater)
     18logical,save :: calltherm,callrichsl,callslope,tituscap
     19!$OMP THREADPRIVATE(calltherm,callrichsl,callslope,tituscap)
     20logical,save :: callyamada4,callatke
     21!$OMP THREADPRIVATE(callyamada4,callatke)
     22logical,save :: callemis
     23logical,save :: callg2d
     24!$OMP THREADPRIVATE(callemis,callg2d)
     25logical,save :: linear ! ?!?
     26!$OMP THREADPRIVATE(linear)
     27logical,save :: gwd_convective_source
     28!$OMP THREADPRIVATE(gwd_convective_source)
    4329
    44       logical startphy_file
     30real,save :: semi ! ?!?
     31!$OMP THREADPRIVATE(semi)
     32real,save :: alphan ! ?!?
     33!$OMP THREADPRIVATE(alphan)
     34real,save :: fixed_euv_value
     35!$OMP THREADPRIVATE(fixed_euv_value)
     36real,save :: euveff
     37!$OMP THREADPRIVATE(euveff)
     38real,save :: tke_heat_flux
     39!$OMP THREADPRIVATE(tke_heat_flux)
     40real,save :: coeff_injection ! dust injection scheme coefficient
     41!$OMP THREADPRIVATE(coeff_injection)
     42real,save :: ti_injection ! local time of beginning injection
     43real,save :: tf_injection ! local time of end injection
     44!$OMP THREADPRIVATE(ti_injection,tf_injection)
     45real,save :: coeff_detrainment ! rocket dust detrainment coefficient
     46!$OMP THREADPRIVATE(coeff_detrainment)
     47real,save :: CLFfixval
     48!$OMP THREADPRIVATE(CLFfixval)
    4549
    46       logical callemis
    47       logical callg2d
    48       logical linear
    49       logical gwd_convective_source
     50integer,save :: iaervar
     51!$OMP THREADPRIVATE(iaervar)
     52integer,save :: iradia
     53!$OMP THREADPRIVATE(iradia)
     54integer,save :: ilwd
     55integer,save :: ilwb
     56integer,save :: ilwn
     57!$OMP THREADPRIVATE(ilwd,ilwb,ilwn)
     58integer,save :: ncouche
     59!$OMP THREADPRIVATE(ncouche)
     60integer,save :: solvarmod   ! model for solar EUV variation
     61!$OMP THREADPRIVATE(solvarmod)
     62integer,save :: solvaryear  ! mars year for realisticly varying solar EUV
     63!$OMP THREADPRIVATE(solvaryear)
     64integer,save :: dustinjection ! dust injection scheme number
     65!$OMP THREADPRIVATE(dustinjection)
    5066
    51       real semi
    52       real alphan
    53       real fixed_euv_value
    54       real euveff
    55       real tke_heat_flux
    56       real coeff_injection ! dust injection scheme coefficient
    57       real ti_injection ! local time of beginning injection
    58       real tf_injection ! local time of end injection
    59       real coeff_detrainment ! rocket dust detrainment coefficient
    60       real CLFfixval
     67logical,save :: rayleigh
     68!$OMP THREADPRIVATE(rayleigh)
     69logical,save :: scavenging
     70!$OMP THREADPRIVATE(scavenging)
     71logical,save :: rdstorm ! rocket dust storm parametrization
     72!$OMP THREADPRIVATE(rdstorm)
     73logical,save :: topflows ! entrainment by mountain top dust flows parametrization
     74!$OMP THREADPRIVATE(topflows)
     75logical,save :: latentheat_surfwater ! latent heat release from ground water ice sublimation/condensation
     76!$OMP THREADPRIVATE(latentheat_surfwater)
     77logical,save :: cst_cap_albedo ! polar cap albedo remains unchanged by water frost deposition
     78!$OMP THREADPRIVATE(cst_cap_albedo)
     79logical,save :: temp_dependent_m ! temperature-dependent water contact parameter
     80!$OMP THREADPRIVATE(temp_dependent_m)
     81logical,save :: refill_watercap ! h2o_ice_s is converted to watercap when above threshold
     82!$OMP THREADPRIVATE(refill_watercap)
     83logical,save :: cloud_adapt_ts ! adaptative timestep for cloud microphysics
     84!$OMP THREADPRIVATE(cloud_adapt_ts)
     85logical,save :: sedimentation
     86!$OMP THREADPRIVATE(sedimentation)
     87logical,save :: activice,surfaceice_tifeedback,supersat,caps
     88!$OMP THREADPRIVATE(activice,surfaceice_tifeedback,supersat,caps)
     89logical,save :: poreice_tifeedback
     90!$OMP THREADPRIVATE(poreice_tifeedback)
     91logical,save :: co2clouds,co2useh2o,meteo_flux,CLFvaryingCO2,satindexco2
     92!$OMP THREADPRIVATE(co2clouds,co2useh2o,meteo_flux,CLFvaryingCO2,satindexco2)
     93logical,save :: activeco2ice
     94!$OMP THREADPRIVATE(activeco2ice)
     95integer,save :: spantCO2
     96!$OMP THREADPRIVATE(spantCO2)
     97logical,save :: CLFvarying
     98!$OMP THREADPRIVATE(CLFvarying)
     99logical,save :: water
     100!$OMP THREADPRIVATE(water)
     101logical,save :: hdo
     102logical,save :: hdofrac
     103!$OMP THREADPRIVATE(hdo,hdofrac)
     104logical,save :: microphys
     105!$OMP THREADPRIVATE(microphys)
     106logical,save :: photochem
     107!$OMP THREADPRIVATE(photochem)
     108integer,save :: nltemodel
     109!$OMP THREADPRIVATE(nltemodel)
     110integer,save :: nircorr
     111!$OMP THREADPRIVATE(nircorr)
    61112
    62       integer iaervar
    63       integer iradia
    64       integer ilwd
    65       integer ilwb
    66       integer ilwn
    67       integer ncouche
    68       integer solvarmod   ! model for solar EUV variation
    69       integer solvaryear  ! mars year for realisticly varying solar EUV
    70       integer dustinjection ! dust injection scheme number
     113character(len=100),save :: dustiropacity
     114!$OMP THREADPRIVATE(dustiropacity)
     115real,save :: dustrefir
     116!$OMP THREADPRIVATE(dustrefir)
     117 
     118integer,parameter :: swrtype=2 ! type of short wave (solar wavelength) radiative
     119      ! transfer to use 1: Fouquart 2: Toon.
    71120
    72       logical rayleigh
    73       logical scavenging
    74       logical rdstorm ! rocket dust storm parametrization
    75       logical topflows ! entrainment by mountain top dust flows parametrization
    76       logical latentheat_surfwater ! latent heat release from ground water ice sublimation/condensation
    77       logical cst_cap_albedo ! polar cap albedo remains unchanged by water frost deposition
    78       logical temp_dependent_m ! temperature-dependent water contact parameter
    79       logical refill_watercap ! h2o_ice_s is converted to watercap when above threshold
    80       logical cloud_adapt_ts ! adaptative timestep for cloud microphysics
    81       logical sedimentation
    82       logical activice,surfaceice_tifeedback,supersat,caps
    83       logical poreice_tifeedback
    84       logical co2clouds,co2useh2o,meteo_flux,CLFvaryingCO2,satindexco2
    85       logical activeco2ice
    86       integer spantCO2
    87       logical CLFvarying
    88       logical water
    89       logical hdo
    90       logical hdofrac
    91       logical microphys
    92       logical photochem
    93       integer nltemodel
    94       integer nircorr
    95 
    96       character(len=100) dustiropacity
    97       real               dustrefir
    98  
    99       integer swrtype ! type of short wave (solar wavelength) radiative
    100       ! transfer to use 1: Fouquart 2: Toon.
    101       parameter (swrtype=2)
    102 !      parameter (swrtype=2)
     121END MODULE callkeys_mod
  • trunk/LMDZ.MARS/libf/phymars/callradite_mod.F

    r3468 r3726  
    2828      use swmain_mod, only: swmain
    2929      use dust_param_mod, only: doubleq, active, submicron
     30      use callkeys_mod, only: water, activice, rdstorm, topflows,
     31     &                        co2clouds, activeco2ice
    3032      IMPLICIT NONE
    3133c=======================================================================
     
    147149c    -------------
    148150c
    149       include "callkeys.h"
    150151
    151152c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/callsedim_mod.F

    r2628 r3726  
    2727      USE dimradmars_mod, only: naerkind
    2828      USE dust_param_mod, ONLY: doubleq
     29      use callkeys_mod, only: water, activice, microphys, rdstorm,
     30     &                        topflows, co2clouds, co2useh2o,
     31     &                        meteo_flux
    2932      IMPLICIT NONE
    3033
     
    4952c   declarations:
    5053c   -------------
    51      
    52       include "callkeys.h"
    5354
    5455c
  • trunk/LMDZ.MARS/libf/phymars/co2cloud.F90

    r3008 r3726  
    110110  use microphys_h, only: nbinco2_cld, rad_cldco2, mco2
    111111  use write_output_mod, only: write_output
     112  use callkeys_mod, only: sedimentation, CLFvaryingCO2, co2useh2o, &
     113                          satindexco2, meteo_flux
    112114#ifndef MESOSCALE
    113115  use vertical_layers_mod, only: ap, bp
     
    116118  implicit none
    117119
    118   include "callkeys.h"
    119120!----------------------------------------------------------------------------------------------------------------------!
    120121! VARIABLES DECLARATION
  • trunk/LMDZ.MARS/libf/phymars/co2condens_mod.F

    r3586 r3726  
    3838      use comslope_mod, ONLY: subslope_dist,def_slope_mean
    3939      USE paleoclimate_mod, ONLY: paleoclimate
     40      use callkeys_mod, only: caps, co2clouds
    4041
    4142       IMPLICIT NONE
     
    5657c    ------------------
    5758c
    58       include "callkeys.h"
    5959
    6060c-----------------------------------------------------------------------
     
    10271027      use comcstfi_h, only: g
    10281028      use dust_param_mod, only: freedust
     1029      use callkeys_mod, only: water, microphys
    10291030      IMPLICIT NONE
    1030       include "callkeys.h" ! for the flags water and microphys
    10311031c
    10321032c
  • trunk/LMDZ.MARS/libf/phymars/co2snow.F

    r2616 r3726  
    2828
    2929      IMPLICIT NONE
    30 
    31 #include "callkeys.h"
    3230
    3331c=======================================================================
  • trunk/LMDZ.MARS/libf/phymars/compute_dtau_mod.F90

    r2932 r3726  
    2626        USE read_dust_scenario_mod, only: read_dust_scenario
    2727        use write_output_mod, only: write_output
     28        use callkeys_mod, only: iaervar, coeff_injection, ti_injection, &
     29                                tf_injection
    2830       
    2931        IMPLICIT NONE
    30        
    31         include "callkeys.h"
    3232       
    3333        INTEGER, INTENT(in) :: ngrid
  • trunk/LMDZ.MARS/libf/phymars/conc_mod.F90

    r3185 r3726  
    5959         cpnew(:,:)=cpp
    6060         mmean(:,:)=mugaz
    61      return           
     61
    6262 end subroutine init_r_cp_mu
    6363
     
    8686!=======================================================================
    8787
    88 !     declarations
    89  
    90     include "callkeys.h"
    91 
    9288!     input/output
    9389
     
    377373    end do
    378374
    379     return
    380375 end subroutine update_r_cp_mu_ak
    381376
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r3712 r3726  
    4444     &                     ads_massive_ice
    4545      use nonoro_gwd_mix_mod, only: calljliu_gwimix
     46      use callkeys_mod, only: startphy_file, activice, activeco2ice,
     47     &                        alphan, calladj, callatke, callcond,
     48     &                        callconduct, calldifv, callemis,
     49     &                        calleofdump, calleuv, callg2d, calllott,
     50     &                        calllott_nonoro, callmoldiff, callmolvis,
     51     &                        callnirco2, callnlte, callrad, callrichsl,
     52     &                        callslope, callsoil, calltherm, caps,
     53     &                        callthermos, callyamada4, CLFvarying,
     54     &                        CLFvaryingCO2, CLFfixval,
     55     &                        cloud_adapt_ts, co2clouds,
     56     &                        co2useh2o, coeff_detrainment, diurnal,
     57     &                        coeff_injection, dustinjection,
     58     &                        cst_cap_albedo, dustiropacity, dustrefir,
     59     &                        euveff, fixed_euv_value, hdo, hdofrac,
     60     &                        iaervar, ilwb, ilwd, ilwn, iradia,
     61     &                        linear, latentheat_surfwater, microphys,
     62     &                        meteo_flux, ncouche, nircorr, nltemodel,
     63     &                        photochem, poreice_tifeedback, rayleigh,
     64     &                        rdstorm, refill_watercap, satindexco2,
     65     &                        scavenging, season, sedimentation, semi,
     66     &                        solvarmod, solvaryear, spantCO2, supersat,
     67     &                        surfaceice_tifeedback, temp_dependent_m,
     68     &                        tf_injection, ti_injection, thermochem,
     69     &                        thermoswater, tituscap, tke_heat_flux,
     70     &                        topflows, water
    4671
    4772      IMPLICIT NONE
    48 
    49       include "callkeys.h"
    5073
    5174      INTEGER,INTENT(IN) :: ngrid ! number of atmospheric columns
  • trunk/LMDZ.MARS/libf/phymars/convadj.F

    r2823 r3726  
    99     &                      igcm_h2o_vap ! index of water vapor tracer
    1010      use comcstfi_h, only: g
     11      use callkeys_mod, only: water
    1112      implicit none
    1213
     
    2728!
    2829!==================================================================
    29 
    30 !     ------------
    31 !     Declarations
    32 !     ------------
    33 
    34       include "callkeys.h"
    35 
    3630
    3731!     Arguments
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3715 r3726  
    4545use comslope_mod,             only: nslope, subslope_dist, ini_comslope_h, end_comslope_h
    4646use co2condens_mod,           only: CO2cond_ps
     47use callkeys_mod, only: water, photochem, callthermos
    4748! Mostly for XIOS outputs:
    4849use mod_const_mpi,            only: COMM_LMDZ
     
    5152
    5253include "dimensions.h"
    53 include "callkeys.h"
    5454
    5555!=======================================================================
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F90

    r3586 r3726  
    2222use parallel_lmdz,       only: init_parallel
    2323use version_info_mod,    only: print_version_info
     24use callkeys_mod, only: water
    2425
    2526implicit none
     
    4647
    4748include "dimensions.h"
    48 !#include "dimradmars.h"
    49 !#include "comgeomfi.h"
    50 !#include "surfdat.h"
    51 !#include "slope.h"
    52 !#include "comsoil.h"
    53 !#include "comdiurn.h"
    54 include "callkeys.h"
    55 !#include "comsaison.h"
    56 !#include "control.h"
    57 include "netcdf.inc"
    58 !#include "advtrac.h"
    5949
    6050!--------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/hdo_surfex_mod.F

    r3008 r3726  
    1919      use microphys_h, only: molco2, molh2o, molhdo
    2020      use write_output_mod, only: write_output
     21      use callkeys_mod, only: hdofrac
    2122
    2223      implicit none
     
    2526c               for HDO, based of the fluxes for H2O
    2627c           L. Rossi.; M. Vals 2019
    27 c------------------------------------------------------------------
    28       include "callkeys.h"
    2928c------------------------------------------------------------------
    3029c     Arguments:
     
    164163c    &                       ' ',alpha_c)
    165164
    166        return
    167165      end subroutine hdo_surfex
    168166c------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds_mod.F

    r3127 r3726  
    2323      use growthrate_mod, only: growthrate
    2424      use write_output_mod, only: write_output
     25      use callkeys_mod, only: activice, scavenging, cloud_adapt_ts,
     26     &                        hdo, hdofrac
    2527      implicit none
    2628     
     
    4648c           A. Spiga, optimization (February 2012)
    4749c           J. Naar, adaptative subtimestep now done here (June 2023)
    48 c------------------------------------------------------------------
    49       include "callkeys.h"
    5050c------------------------------------------------------------------
    5151c     Inputs/outputs:
  • trunk/LMDZ.MARS/libf/phymars/improvedco2clouds_mod.F90

    r3008 r3726  
    8080  use microphys_h, only: nbinco2_cld, rad_cldco2, m0co2, mco2
    8181  use microphys_h, only: mteta, mtetaco2
     82  use callkeys_mod, only: co2useh2o, meteo_flux
    8283
    8384  implicit none
    84 
    85   include "callkeys.h"
    8685
    8786!----------------------------------------------------------------------------------------------------------------------!
  • trunk/LMDZ.MARS/libf/phymars/initracer.F

    r3027 r3726  
    44       use comcstfi_h, only: pi
    55       use dust_param_mod, only: doubleq, submicron, dustbin
     6       use callkeys_mod, only: water, microphys, scavenging, rdstorm,
     7     &                         topflows, photochem, callthermos, hdo,
     8     &                         callnlte, nltemodel, dustinjection,
     9     &                         co2clouds, co2useh2o, meteo_flux
    610       IMPLICIT NONE
    711c=======================================================================
     
    2428c=======================================================================
    2529
    26 
    27       include "callkeys.h"
    2830
    2931      integer,intent(in) :: ngrid ! number of atmospheric columns
  • trunk/LMDZ.MARS/libf/phymars/lwdiff.F

    r1266 r3726  
    77     &                          ndlo2
    88      use yomlw_h, only: nlaylte
    9       USE comcstfi_h
     9      use comcstfi_h, only: pi
    1010      IMPLICIT NONE
    1111 
    12 #include "callkeys.h"
    13 
    1412C-----------------------------------------------------------------------
    1513C
  • trunk/LMDZ.MARS/libf/phymars/lwflux.F

    r3004 r3726  
    2121      implicit none
    2222 
    23       include "callkeys.h"
    24 
    2523c----------------------------------------------------------------------
    2624c         0.1   arguments
  • trunk/LMDZ.MARS/libf/phymars/lwi.F

    r3004 r3726  
    1414      USE comcstfi_h, ONLY: g, cpp
    1515      USE time_phylmdz_mod, ONLY: dtphys
     16      use callkeys_mod, only: semi, iradia
    1617      implicit none
    1718
    18       include "callkeys.h"
    19  
    2019CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    2120C
  • trunk/LMDZ.MARS/libf/phymars/lwmain_mod.F

    r3004 r3726  
    2323      use lwi_mod, only: lwi
    2424      use lwflux_mod, only: lwflux
     25      use callkeys_mod, only: ilwb, ilwd, ilwn
    2526     
    2627      implicit none
    2728     
    28 c     declarations
    29 c     -------------   
    30       include "callkeys.h"
    31 
    3229c----------------------------------------------------------------------
    3330c         0.1   arguments
  • trunk/LMDZ.MARS/libf/phymars/lwu.F

    r1917 r3726  
    3737      implicit none
    3838
    39       include "callkeys.h"
    40 
    4139c----------------------------------------------------------------------
    4240c         0.1   arguments
  • trunk/LMDZ.MARS/libf/phymars/lwxd.F

    r1917 r3726  
    3434      use dimradmars_mod, only: ndlon, nuco2, nflev, ndlo2
    3535      use yomlw_h, only: nlaylte, xi, xi_emis
     36      use callkeys_mod, only: callemis
    3637      implicit none
    37 
    38       include "callkeys.h"
    3938
    4039c----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/lwxn.F

    r1266 r3726  
    7272      use dimradmars_mod, only: ndlo2, nuco2, ndlon, nflev
    7373      use yomlw_h, only: nlaylte, xi, xi_ground, xi_emis
     74      use callkeys_mod, only: linear, alphan, ncouche
    7475      implicit none
    75 
    76 #include "callkeys.h"
    7776
    7877c----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/nirco2abs.F

    r3712 r3726  
    1313       USE time_phylmdz_mod, ONLY: daysec
    1414       use nirdata_mod, only: npres, alfa, corgcm, oco21d, pres1d
     15       use callkeys_mod, only: diurnal, nircorr
    1516       IMPLICIT NONE
    1617c=======================================================================
     
    5556c    ------------------
    5657c
    57       include "callkeys.h"
    5858
    5959c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/nltecool.F

    r3016 r3726  
    193193      use tracer_mod, only: igcm_co2, igcm_co, igcm_o, igcm_n2, mmol
    194194      use conc_mod, only: mmean
     195      use callkeys_mod, only: nltemodel
    195196      implicit none
    196 
    197       include "callkeys.h"
    198197
    199198c Input and output variables
  • trunk/LMDZ.MARS/libf/phymars/nlthermeq.F

    r3016 r3726  
    1616      use yomlw_h, only: nlaylte
    1717      use nlteparams_h, only: ptrans, pminte, zw
     18      use callkeys_mod, only: callnlte
    1819      implicit none
    19       include "callkeys.h"
    2020
    2121c
     
    2626c
    2727c     Local:
    28       integer igpmax, ismax
    29       logical firstcall
    30 
     28      integer ismax
     29      integer,save :: igpmax
     30      logical,save :: firstcall = .true.
    3131!$OMP THREADPRIVATE(firstcall,igpmax)
    3232
    33       data firstcall /.true./
    34       save firstcall, igpmax
    3533c
    3634      if(firstcall) then
  • trunk/LMDZ.MARS/libf/phymars/nonoro_gwd_mix_mod.F90

    r3398 r3726  
    3636      use geometry_mod, only: cell_area
    3737      use write_output_mod, only: write_output
    38 #ifdef CPP_XIOS
    39      use xios_output_mod, only: send_xios_field
    40 #endif     
    4138     
    4239      implicit none
    43       include "callkeys.h"
    4440
    4541      CHARACTER (LEN=20) :: modname='NONORO_GWD_MIX'
  • trunk/LMDZ.MARS/libf/phymars/nonoro_gwd_ran_mod.F90

    r3263 r3726  
    4848      use geometry_mod, only: cell_area
    4949      use write_output_mod, only: write_output
    50 #ifdef CPP_XIOS
    51      use xios_output_mod, only: send_xios_field
    52 #endif     
    5350     
    5451      implicit none
    55       include "callkeys.h"
    5652
    5753      CHARACTER (LEN=20) :: modname='nonoro_gwd_ran'
  • trunk/LMDZ.MARS/libf/phymars/nuclea.F

    r3064 r3726  
    99      use microphys_h, only: nbin_cld, rad_cld, nav, mteta, m0
    1010      use microphys_h, only: desorp, kbz, nus, rgp, surfdif, vo1
     11      use callkeys_mod, only: temp_dependent_m, cloud_adapt_ts
    1112      implicit none
    1213*                                                     *
     
    2021*     Optimisation by A. Spiga (February 2012)        * 
    2122*******************************************************
    22 
    23       include "callkeys.h"
    2423
    2524c     Inputs
  • trunk/LMDZ.MARS/libf/phymars/nucleaco2.F90

    r3008 r3726  
    2929 ! nucrate_h2o en sortie aussi :
    3030!nucleation sur dust et h2o separement ici
    31 
    32 include "callkeys.h"
    3331
    3432!     Inputs
  • trunk/LMDZ.MARS/libf/phymars/pbl_parameters_mod.F90

    r3325 r3726  
    2828      use watersat_mod, only: watersat
    2929      use paleoclimate_mod, only: include_waterbuoyancy
     30      use callkeys_mod, only: calladj, calltherm, callatke
    3031
    3132      IMPLICIT NONE
     
    7980!   Declarations:
    8081!   -------------
    81 
    82 #include "callkeys.h"
    8382
    8483!   Arguments:
  • trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90

    r3619 r3726  
    3434use comcstfi_h,          only: pi
    3535use geometry_mod,        only: latitude
     36use callkeys_mod, only: startphy_file, rdstorm, hdo
    3637
    3738implicit none
    38 
    39 include "callkeys.h"
    4039
    4140!======================================================================
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r3619 r3726  
    221221  use comslope_mod, only: nslope
    222222  use paleoclimate_mod, only: paleoclimate
     223  use callkeys_mod, only: calltherm, dustinjection, calllott_nonoro
    223224  implicit none
    224  
    225   include "callkeys.h"
    226225 
    227226  character(len=*),intent(in) :: filename
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3612 r3726  
    128128      use lmdz_atke_turbulence_ini, only : atke_ini
    129129      use waterice_tifeedback_mod, only : waterice_tifeedback
     130      use callkeys_mod, only: calladj, calltherm, callatke, calldifv
     131      use callkeys_mod, only: callrichsl, tke_heat_flux
     132      use callkeys_mod, only: calllott, calllott_nonoro, calleofdump
     133      use callkeys_mod, only: callrad, callnlte, callnirco2, nircorr
     134      use callkeys_mod, only: diurnal, season, iradia, nltemodel
     135      use callkeys_mod, only: water, activice, microphys, CLFvarying
     136      use callkeys_mod, only: hdo, co2clouds, co2useh2o, meteo_flux
     137      use callkeys_mod, only: callsoil, callslope, callcond
     138      use callkeys_mod, only: tituscap, surfaceice_tifeedback
     139      use callkeys_mod, only: refill_watercap, poreice_tifeedback
     140      use callkeys_mod, only: cst_cap_albedo
     141      use callkeys_mod, only: rdstorm, dustinjection
     142      use callkeys_mod, only: topflows, dustiropacity
     143      use callkeys_mod, only: sedimentation, scavenging
     144      use callkeys_mod, only: photochem, callthermos
     145      use callkeys_mod, only: startphy_file
     146
    130147      IMPLICIT NONE
    131148c=======================================================================
     
    229246c    ------------------
    230247
    231       include "callkeys.h"
    232248      include "netcdf.inc"
    233249
  • trunk/LMDZ.MARS/libf/phymars/read_dust_scenario_mod.F90

    r2921 r3726  
    1515use planete_h, only: year_day
    1616USE mod_phys_lmdz_transfert_para, ONLY: bcast
     17use callkeys_mod, only: iaervar, dustinjection, swrtype
     18
    1719implicit none
    18 
    19 include "callkeys.h"
    2020
    2121integer, intent(in) :: ngrid,nlayer
     
    6666   radeg=180/pi
    6767   
    68    ! assimilated dust file: (NB: iaervar is a common in "callkeys.h")
    6968   ! iaervar=4 means read dust_tes.nc file
    7069   ! iaervar=6 means read dust_cold.nc file
     
    386385endif
    387386
    388 if (swrtype.eq.1) then ! Fouquart (NB: swrtype is set in callkeys.h)
     387if (swrtype.eq.1) then ! Fouquart (NB: swrtype is set in callkeys_mod)
    389388 ! when using old radiative transfer (like in MCD 4.x)
    390389 ! needed to decrease opacity (*0.825) to compensate overestimation of
  • trunk/LMDZ.MARS/libf/phymars/rocketduststorm_mod.F90

    r2963 r3726  
    4545      USE callradite_mod, only: callradite
    4646      use write_output_mod, only: write_output
     47      use callkeys_mod, only: coeff_detrainment
    4748      IMPLICIT NONE
    48 
    49       include "callkeys.h"
    5049
    5150!--------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/simpleclouds.F

    r2378 r3726  
    33     &             pq,pdq,pdqcloud,pdtcloud,
    44     &             nq,tau,rice)
    5       USE updaterad
     5      USE updaterad, ONLY: updaterice_typ
    66      USE watersat_mod, ONLY: watersat
    77      use tracer_mod, only: igcm_h2o_vap, igcm_h2o_ice,
    88     &                      igcm_hdo_vap, igcm_hdo_ice,
    99     &                      qperemin
    10       USE comcstfi_h
     10      use comcstfi_h, only: cpp
    1111      use dimradmars_mod, only: naerkind
     12      use callkeys_mod, only: hdo, hdofrac
    1213
    1314      implicit none
     
    3435c                            simpleclouds.F, and corrected calculations
    3536c                            of the typical CCN profile, Oct. 2011)
    36 c------------------------------------------------------------------
    37 #include "callkeys.h"
    38 
    3937c------------------------------------------------------------------
    4038c     Arguments:
     
    233231c     endif !hdo
    234232c------------------------------------------------------------------
    235       return
    236233      end
  • trunk/LMDZ.MARS/libf/phymars/soil.F

    r3230 r3726  
    99      use surfdat_h, only: watercaptag, inert_h2o_ice
    1010      use comslope_mod, ONLY: nslope
     11      use callkeys_mod, only: surfaceice_tifeedback, poreice_tifeedback
    1112      implicit none
    1213
     
    1920!        heat capacity are commons in comsoil_h
    2021!-----------------------------------------------------------------------
    21 
    22 #include "callkeys.h"
    2322
    2423c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/soilwater.F90

    r3568 r3726  
    66      use comsoil_h, only: igcm_h2o_vap_soil, igcm_h2o_ice_soil, igcm_h2o_vap_ads, layer, mlayer, choice_ads, porosity_reg, &
    77                           ads_const_D, ads_massive_ice
    8       use comcstfi_h
    9       use tracer_mod
     8      use comcstfi_h, only: pi, r
     9      use tracer_mod, only: igcm_h2o_vap
    1010      use surfdat_h, only: watercaptag ! use mis par AP15 essai
    1111      use geometry_mod, only: cell_area, latitude_deg
     
    4646!
    4747! =================================================================================================  =
    48 
    49 ! Libraries :
    50 ! ===========  =
    51 !#include "dimensions.h"
    52 !#include "dimphys.h"
    53 !#include "comsoil.h"
    54 #include "callkeys.h"
    55 !#include "comcstfi.h"
    56 !#include "tracer.h"
    57 !#include "watercap.h"
    58 
    5948
    6049! Arguments :
     
    16361625!endif
    16371626endif
    1638 RETURN
     1627
    16391628END
    16401629
  • trunk/LMDZ.MARS/libf/phymars/suaer.F90

    r2584 r3726  
    1414use datafile_mod, only: datadir
    1515USE mod_phys_lmdz_transfert_para, ONLY: bcast
     16use callkeys_mod, only: dustrefir
     17
    1618IMPLICIT NONE
    1719!==================================================================
     
    4345!   
    4446!==================================================================
    45 
    46 ! Includes:
    47 
    48 include "callkeys.h"
    4947
    5048! Optical properties (read in external ASCII files)
  • trunk/LMDZ.MARS/libf/phymars/surfini_mod.F90

    r3142 r3726  
    2424      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat
    2525      use datafile_mod, only: datadir
     26      use callkeys_mod, only: water
    2627
    2728      IMPLICIT NONE
     
    3435!   Declarations:
    3536!   -------------
    36       include "callkeys.h"
    3737
    3838      integer,intent(in) :: ngrid ! number of atmospheric columns
  • trunk/LMDZ.MARS/libf/phymars/swmain_mod.F

    r2311 r3726  
    1414     &                          nsun,naerkind
    1515      use yomlw_h, only: nlaylte, gcp
     16      use callkeys_mod, only: swrtype
    1617      IMPLICIT NONE
    1718
    18 c     DECLARATIONS
    19 c     -------------     
    20       include "callkeys.h"
    2119c     
    2220c     PURPOSE.
     
    146144      DO INU = 1,2
    147145
    148 ! NB: swrtype is set in callkeys.h
     146! NB: swrtype is set in callkeys_mod
    149147        if (swrtype.eq.1) then ! Fouquart
    150148          CALL SWR_FOUQUART( KDLON, kflev, INU
  • trunk/LMDZ.MARS/libf/phymars/swr_fouquart.F

    r1266 r3726  
    77     &                          ndlon, nflev, naerkind
    88      use yomlw_h, only: nlaylte
     9      use callkeys_mod, only: rayleigh
    910      IMPLICIT NONE
    1011C     
    11 #include "callkeys.h"
    12 
    1312C     
    1413C   SWR - Continuum scattering computations
  • trunk/LMDZ.MARS/libf/phymars/swr_toon.F

    r1266 r3726  
    77     &                          ndlon, naerkind
    88      use yomlw_h, only: nlaylte
     9      use callkeys_mod, only: rayleigh
    910     
    1011      IMPLICIT NONE
    1112C     
    12 #include "callkeys.h"
    13 
    1413C     
    1514C   SWR - Continuum scattering computations
  • trunk/LMDZ.MARS/libf/phymars/updatereffrad_mod.F

    r2660 r3726  
    2929     &            iaer_stormdust_doubleq,iaer_topdust_doubleq
    3030       use dust_param_mod, only: doubleq, active
     31       use callkeys_mod, only: water, activice, microphys
     32       use callkeys_mod, only: rdstorm, topflows
     33       use callkeys_mod, only: co2clouds, activeco2ice, co2useh2o
    3134       IMPLICIT NONE
    3235c=======================================================================
     
    5154c    -------------
    5255c
    53       include "callkeys.h"
    5456
    5557c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/vdif_cd_mod.F90

    r3333 r3726  
    1818   SUBROUTINE vdif_cd(ngrid,nlay,nslope,pz0,pg,pz,pp,pu,pv,wstar,pts,ph,mumean,pqvap,pqsurf,write_outputs,pcdv,pcdh)
    1919   
    20    use comcstfi_h
    2120   use turb_mod, only: turb_resolved
    2221   use watersat_mod, only: watersat
     
    2524   use write_output_mod, only: write_output
    2625   use comslope_mod, ONLY: iflat
     26   use callkeys_mod, only: callrichsl, callatke
    2727   IMPLICIT NONE
    28    include "callkeys.h"     
    29 
    3028
    3129!=======================================================================
  • trunk/LMDZ.MARS/libf/phymars/vdifc_mod.F

    r3619 r3726  
    4040      use lmdz_call_atke, only: call_atke
    4141      use dust_windstress_lift_mod, only: dust_windstress_lift
     42      use callkeys_mod, only: callcond, callrichsl, callyamada4,
     43     &                        callatke, tke_heat_flux, water, hdo,
     44     &                        co2clouds, rdstorm, dustinjection,
     45     &                        latentheat_surfwater
    4246      IMPLICIT NONE
    4347
     
    6165c   declarations:
    6266c   -------------
    63 
    64       include "callkeys.h"
    6567
    6668c
  • trunk/LMDZ.MARS/libf/phymars/watercloud_mod.F

    r2984 r3726  
    2929      use conc_mod, only: mmean
    3030      use write_output_mod, only: write_output
     31      use callkeys_mod, only: activice, microphys, supersat, hdo
     32      use callkeys_mod, only: scavenging, CLFvarying
    3133      IMPLICIT NONE
    3234
     
    5456c   declarations:
    5557c   -------------
    56 
    57       include "callkeys.h"
    5858
    5959c   Inputs/outputs:
  • trunk/LMDZ.MARS/libf/phymars/waterice_tifeedback_mod.F90

    r3262 r3726  
    2828      use comsoil_h, only: layer, inertiedat, porosity_reg
    2929      use surfdat_h, only: watercaptag, inert_h2o_ice
     30      use callkeys_mod, only: poreice_tifeedback, surfaceice_tifeedback
    3031      IMPLICIT NONE
    31       include "callkeys.h"
     32
    3233!=======================================================================
    3334!   Description :
  • trunk/LMDZ.MARS/libf/phymars/yamada4.F

    r2823 r3726  
    612612!     print*,'OKFIN'
    613613      first=.false.
    614       return
     614
    615615      end
    616616      SUBROUTINE vdif_q2(timestep,gravity,rconst,ngrid,nlay
    617617     & ,plev,temp,kmy,q2)
     618!.......................................................................
    618619      IMPLICIT NONE
    619 !.......................................................................
    620 ! MARS
    621       include "callkeys.h"
    622620!.......................................................................
    623621!
     
    694692      SUBROUTINE vdif_q2e(timestep,gravity,rconst,ngrid,nlay,
    695693     &   plev,temp,kmy,q2)
     694!.......................................................................
    696695      IMPLICIT NONE
    697 !.......................................................................
    698 ! MARS
    699       include "callkeys.h"
    700696!.......................................................................
    701697!
     
    753749      enddo
    754750
    755       return
     751
    756752      end
Note: See TracChangeset for help on using the changeset viewer.