source: LMDZ5/trunk/libf/phylmd/conf_phys_m.F90 @ 2945

Last change on this file since 2945 was 2945, checked in by jbmadeleine, 7 years ago
  • Added a new output called rneblsvol which is the cloud fraction by volume

computed in the thermals (see cloudth_vert in cloudth_mod.F90)

  • Added an option called iflag_rain_incloud_vol that computes the conversion

of cloud water to rain using the cloud fraction by volume instead of the cloud
fraction by area, which is larger and otherwise erroneously reduces the in-cloud
water content; iflag_rain_incloud_vol can only be used for iflag_cloudth_vert>=3

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 79.4 KB
RevLine 
[1687]1!
2! $Id: conf_phys.F90 1668 2012-10-12 10:47:37Z idelkadi $
3!
4!
5!
[2702]6MODULE conf_phys_m
[1687]7
[2702]8  IMPLICIT NONE
[1687]9
[2702]10CONTAINS
[1687]11
[2702]12  SUBROUTINE conf_phys(ok_journe, ok_mensuel, ok_instan, ok_hf, &
[1938]13       ok_LES,&
14       callstats,&
15       solarlong0,seuil_inversion, &
16       fact_cldcon, facttemps,ok_newmicro,iflag_radia,&
[2236]17       iflag_cld_th, &
[1938]18       iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
[2738]19       ok_ade, ok_aie, ok_alw, ok_cdnc, aerosol_couple, &
[1938]20       flag_aerosol, flag_aerosol_strat, new_aod, &
[2644]21       flag_bc_internal_mixture, bl95_b0, bl95_b1,&
[1938]22       read_climoz, &
23       alp_offset)
[1687]24
[2702]25    USE IOIPSL
[1938]26    USE surface_data
27    USE phys_cal_mod
[2702]28    USE carbon_cycle_mod,  ONLY: carbon_cycle_tr, carbon_cycle_cpl
29    USE mod_grid_phy_lmdz, ONLY: klon_glo
[2311]30    USE print_control_mod, ONLY: lunout
[1687]31
[1938]32    include "conema3.h"
33    include "fisrtilp.h"
34    include "nuage.h"
35    include "YOMCST.h"
36    include "YOMCST2.h"
[1687]37
[1938]38    include "thermcell.h"
[1687]39
[2287]40
[1938]41    !IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12
42    include "clesphys.h"
43    include "compbl.h"
44    include "comsoil.h"
45    include "YOEGWD.h"
46    !
47    ! Configuration de la "physique" de LMDZ a l'aide de la fonction
48    ! GETIN de IOIPSL
49    !
50    ! LF 05/2001
51    !
[1687]52
[1938]53    !
54    ! type_ocean:      type d'ocean (force, slab, couple)
55    ! version_ocean:   version d'ocean (opa8/nemo pour type_ocean=couple ou
[2057]56    !                                   sicOBS,sicINT,sicNO pour type_ocean=slab)
[1938]57    ! ok_veget:   type de modele de vegetation
58    ! ok_journe:  sorties journalieres
59    ! ok_hf:  sorties haute frequence
60    ! ok_mensuel: sorties mensuelles
61    ! ok_instan:  sorties instantanees
62    ! ok_ade, ok_aie: apply or not aerosol direct and indirect effects
[2738]63    ! ok_alw: activate aerosol LW effect
[1938]64    ! ok_cdnc, ok cloud droplet number concentration
65    ! flag_aerosol_strat : flag pour les aerosols stratos
[2644]66    ! flag_bc_internal_mixture : use BC internal mixture if true
[1938]67    ! bl95_b*: parameters in the formula to link CDNC to aerosol mass conc
68    !
[1687]69
70
[1938]71    ! Sortie:
[2702]72    LOGICAL              :: ok_newmicro
73    INTEGER              :: iflag_radia
74    LOGICAL              :: ok_journe, ok_mensuel, ok_instan, ok_hf
75    LOGICAL              :: ok_LES
[1938]76    LOGICAL              :: callstats
[2738]77    LOGICAL              :: ok_ade, ok_aie, ok_alw, ok_cdnc, aerosol_couple
[1938]78    INTEGER              :: flag_aerosol
[2530]79    INTEGER              :: flag_aerosol_strat
[2644]80    LOGICAL              :: flag_bc_internal_mixture
[1938]81    LOGICAL              :: new_aod
82    REAL                 :: bl95_b0, bl95_b1
[2702]83    REAL                 :: fact_cldcon, facttemps,ratqsbas,ratqshaut,tau_ratqs
84    INTEGER              :: iflag_cld_th
85    INTEGER              :: iflag_ratqs
[1687]86
[2702]87    CHARACTER (len = 6), SAVE  :: type_ocean_omp, version_ocean_omp, ocean_omp
88    CHARACTER (len = 10),SAVE  :: type_veget_omp
89    CHARACTER (len = 8), SAVE  :: aer_type_omp
90    LOGICAL, SAVE       :: ok_snow_omp
91    LOGICAL, SAVE       :: ok_newmicro_omp
92    LOGICAL, SAVE       :: ok_all_xml_omp
93    LOGICAL, SAVE       :: ok_journe_omp, ok_mensuel_omp, ok_instan_omp, ok_hf_omp       
94    LOGICAL, SAVE       :: ok_LES_omp   
95    LOGICAL, SAVE       :: callstats_omp
[2738]96    LOGICAL, SAVE       :: ok_ade_omp, ok_aie_omp, ok_alw_omp, ok_cdnc_omp, aerosol_couple_omp
[1938]97    INTEGER, SAVE       :: flag_aerosol_omp
[2530]98    INTEGER, SAVE       :: flag_aerosol_strat_omp
[2644]99    LOGICAL, SAVE       :: flag_bc_internal_mixture_omp
[1938]100    LOGICAL, SAVE       :: new_aod_omp
101    REAL,SAVE           :: bl95_b0_omp, bl95_b1_omp
102    REAL,SAVE           :: freq_ISCCP_omp, ecrit_ISCCP_omp
[2580]103    REAL,SAVE           :: freq_COSP_omp, freq_AIRS_omp
[2702]104    REAL,SAVE           :: fact_cldcon_omp, facttemps_omp,ratqsbas_omp
105    REAL,SAVE           :: tau_cld_cv_omp, coefw_cld_cv_omp
106    INTEGER, SAVE       :: iflag_cld_cv_omp
[2205]107
108
[2702]109    REAL, SAVE          :: ratqshaut_omp
110    REAL, SAVE          :: tau_ratqs_omp
[2075]111    REAL, SAVE          :: t_coupl_omp
[2702]112    INTEGER, SAVE       :: iflag_radia_omp
113    INTEGER, SAVE       :: iflag_rrtm_omp
114    INTEGER, SAVE       :: iflag_albedo_omp !albedo SB
115    LOGICAL, SAVE       :: ok_chlorophyll_omp ! albedo SB 
116    INTEGER, SAVE       :: NSW_omp
117    INTEGER, SAVE       :: iflag_cld_th_omp, ip_ebil_phy_omp
118    INTEGER, SAVE       :: iflag_ratqs_omp
[1687]119
[2704]120    REAL, SAVE          :: f_cdrag_ter_omp,f_cdrag_oce_omp
121    REAL, SAVE          :: f_rugoro_omp   , z0min_omp
122    REAL, SAVE          :: z0m_seaice_omp,z0h_seaice_omp
[2702]123    REAL, SAVE          :: min_wind_speed_omp,f_gust_wk_omp,f_gust_bl_omp,f_qsat_oce_omp, f_z0qh_oce_omp
124    INTEGER, SAVE       :: iflag_gusts_omp,iflag_z0_oce_omp
[1687]125
[1938]126    ! Local
[2702]127    REAL                 :: zzz
[1687]128
[2702]129    REAL :: seuil_inversion
130    REAL,SAVE :: seuil_inversion_omp
[1687]131
[2702]132    INTEGER,SAVE :: iflag_thermals_ed_omp,iflag_thermals_optflux_omp,iflag_thermals_closure_omp
133    REAL, SAVE :: fact_thermals_ed_dz_omp
134    INTEGER,SAVE :: iflag_thermals_omp,nsplit_thermals_omp
135    REAL,SAVE :: tau_thermals_omp,alp_bl_k_omp
[1938]136    ! nrlmd le 10/04/2012
[2702]137    INTEGER,SAVE :: iflag_trig_bl_omp,iflag_clos_bl_omp
138    INTEGER,SAVE :: tau_trig_shallow_omp,tau_trig_deep_omp
139    REAL,SAVE    :: s_trig_omp
[1938]140    ! fin nrlmd le 10/04/2012
[2702]141    REAL :: alp_offset
[1938]142    REAL, SAVE :: alp_offset_omp
[2702]143    INTEGER,SAVE :: iflag_coupl_omp,iflag_clos_omp,iflag_wake_omp
144    INTEGER,SAVE :: iflag_cvl_sigd_omp
[2201]145    REAL, SAVE :: coef_clos_ls_omp
[1938]146    REAL, SAVE :: supcrit1_omp, supcrit2_omp
147    INTEGER, SAVE :: iflag_mix_omp
[2420]148    INTEGER, SAVE :: iflag_mix_adiab_omp
[2702]149    REAL, SAVE :: scut_omp, qqa1_omp, qqa2_omp, gammas_omp, Fmax_omp, alphas_omp
[2287]150    REAL, SAVE :: tmax_fonte_cv_omp
[1687]151
[1938]152    REAL,SAVE :: R_ecc_omp,R_peri_omp,R_incl_omp,solaire_omp
[2524]153    LOGICAL,SAVE :: ok_suntime_rrtm_omp
[1938]154    REAL,SAVE :: co2_ppm_omp, RCO2_omp, co2_ppm_per_omp, RCO2_per_omp
155    REAL,SAVE :: CH4_ppb_omp, RCH4_omp, CH4_ppb_per_omp, RCH4_per_omp
156    REAL,SAVE :: N2O_ppb_omp, RN2O_omp, N2O_ppb_per_omp, RN2O_per_omp
157    REAL,SAVE :: CFC11_ppt_omp,RCFC11_omp,CFC11_ppt_per_omp,RCFC11_per_omp
158    REAL,SAVE :: CFC12_ppt_omp,RCFC12_omp,CFC12_ppt_per_omp,RCFC12_per_omp
159    LOGICAL,SAVE :: ok_4xCO2atm_omp
160    REAL,SAVE :: epmax_omp
[2481]161    REAL,SAVE :: coef_epmax_cape_omp
[1938]162    LOGICAL,SAVE :: ok_adj_ema_omp
163    INTEGER,SAVE :: iflag_clw_omp
164    REAL,SAVE :: cld_lc_lsc_omp,cld_lc_con_omp,cld_tau_lsc_omp,cld_tau_con_omp
165    REAL,SAVE :: ffallv_lsc_omp, ffallv_con_omp,coef_eva_omp
166    LOGICAL,SAVE :: reevap_ice_omp
167    INTEGER,SAVE :: iflag_pdf_omp
168    INTEGER,SAVE :: iflag_ice_thermo_omp
[2006]169    INTEGER,SAVE :: iflag_t_glace_omp
[2547]170    INTEGER,SAVE :: iflag_cloudth_vert_omp
[2945]171    INTEGER,SAVE :: iflag_rain_incloud_vol_omp
[1938]172    REAL,SAVE :: rad_froid_omp, rad_chau1_omp, rad_chau2_omp
173    REAL,SAVE :: t_glace_min_omp, t_glace_max_omp
[2006]174    REAL,SAVE :: exposant_glace_omp
[1938]175    REAL,SAVE :: rei_min_omp, rei_max_omp
[2915]176    INTEGER,SAVE :: iflag_sic_omp
177    REAL,SAVE :: inertie_sol_omp,inertie_sno_omp,inertie_sic_omp
178    REAL,SAVE :: inertie_lic_omp
[1938]179    REAL,SAVE :: qsol0_omp
180    REAL,SAVE :: evap0_omp
181    REAL,SAVE :: albsno0_omp
182    REAL      :: solarlong0
183    REAL,SAVE :: solarlong0_omp
184    INTEGER,SAVE :: top_height_omp,overlap_omp
[2126]185    REAL,SAVE :: cdmmax_omp,cdhmax_omp,ksta_omp,ksta_ter_omp,f_ri_cd_min_omp
[1938]186    LOGICAL,SAVE :: ok_kzmin_omp
[2561]187    REAL, SAVE   :: pbl_lmixmin_alpha_omp
[1938]188    REAL, SAVE ::  fmagic_omp, pmagic_omp
189    INTEGER,SAVE :: iflag_pbl_omp,lev_histhf_omp,lev_histday_omp,lev_histmth_omp
[2159]190    INTEGER,SAVE :: iflag_pbl_split_omp
[2455]191    INTEGER,SAVE :: iflag_order2_sollw_omp
[2704]192    INTEGER, SAVE :: lev_histins_omp, lev_histLES_omp
[1938]193    INTEGER, SAVE :: lev_histdayNMC_omp
194    INTEGER, SAVE :: levout_histNMC_omp(3)
195    LOGICAL, SAVE :: ok_histNMC_omp(3)
196    REAL, SAVE :: freq_outNMC_omp(3), freq_calNMC_omp(3)
197    CHARACTER*4, SAVE :: type_run_omp
[2580]198    LOGICAL,SAVE :: ok_cosp_omp, ok_airs_omp
[1938]199    LOGICAL,SAVE :: ok_mensuelCOSP_omp,ok_journeCOSP_omp,ok_hfCOSP_omp
200    REAL,SAVE :: lonmin_ins_omp, lonmax_ins_omp, latmin_ins_omp, latmax_ins_omp
201    REAL,SAVE :: ecrit_hf_omp, ecrit_day_omp, ecrit_mth_omp, ecrit_reg_omp
202    REAL,SAVE :: ecrit_ins_omp
203    REAL,SAVE :: ecrit_LES_omp
204    REAL,SAVE :: ecrit_tra_omp
[2253]205    REAL,SAVE :: cvl_comp_threshold_omp
206    REAL,SAVE :: cvl_sig2feed_omp
[1938]207    REAL,SAVE :: cvl_corr_omp
208    LOGICAL,SAVE :: ok_lic_melt_omp
209    !
[2702]210    LOGICAL,SAVE  :: cycle_diurne_omp,soil_model_omp,new_oliq_omp
211    LOGICAL,SAVE  :: ok_orodr_omp, ok_orolf_omp, ok_limitvrai_omp
[1938]212    INTEGER, SAVE :: nbapp_rad_omp, iflag_con_omp
[2730]213    INTEGER, SAVE :: nbapp_cv_omp, nbapp_wk_omp
[1938]214    INTEGER, SAVE :: iflag_ener_conserv_omp
[2007]215    LOGICAL, SAVE :: ok_conserv_q_omp
[1938]216    INTEGER, SAVE :: iflag_fisrtilp_qsat_omp
[2415]217    INTEGER, SAVE :: iflag_bergeron_omp
[2702]218    LOGICAL,SAVE  :: ok_strato_omp
219    LOGICAL,SAVE  :: ok_hines_omp, ok_gwd_rando_omp
220    REAL, SAVE    :: gwd_rando_ruwmax_omp, gwd_rando_sat_omp
221    REAL, SAVE    :: gwd_front_ruwmax_omp, gwd_front_sat_omp
222    REAL, SAVE    :: sso_gkdrag_omp,sso_grahil_omp,sso_grcrit_omp
223    REAL, SAVE    :: sso_gfrcri_omp,sso_gkwake_omp,sso_gklift_omp
224    LOGICAL,SAVE  :: ok_qch4_omp
225    LOGICAL,SAVE  :: carbon_cycle_tr_omp
226    LOGICAL,SAVE  :: carbon_cycle_cpl_omp
[2788]227    LOGICAL,SAVE  :: adjust_tropopause_omp
228    LOGICAL,SAVE  :: ok_daily_climoz_omp
[1687]229
[2702]230    INTEGER, INTENT(OUT):: read_climoz ! read ozone climatology, OpenMP shared
[1938]231    ! Allowed values are 0, 1 and 2
232    ! 0: do not read an ozone climatology
233    ! 1: read a single ozone climatology that will be used day and night
234    ! 2: read two ozone climatologies, the average day and night
235    ! climatology and the daylight climatology
[1687]236
[1938]237    !-----------------------------------------------------------------
[1687]238
[2357]239    print*,'CONFPHYS ENTREE'
[1938]240    !$OMP MASTER
241    !Config Key  = type_ocean
242    !Config Desc = Type d'ocean
243    !Config Def  = force
244    !Config Help = Type d'ocean utilise: force, slab,couple
245    !
246    type_ocean_omp = 'force '
[2702]247    CALL getin('type_ocean', type_ocean_omp)
[1938]248    !
249    !Config Key  = version_ocean
250    !Config Desc = Version d'ocean
251    !Config Def  = xxxxxx
252    !Config Help = Version d'ocean utilise: opa8/nemo/sicOBS/xxxxxx
253    !
254    version_ocean_omp = 'xxxxxx'
[2702]255    CALL getin('version_ocean', version_ocean_omp)
[1687]256
[1938]257    !Config Key  = OCEAN
258    !Config Desc = Old parameter name for type_ocean
259    !Config Def  = yyyyyy
260    !Config Help = This is only for testing purpose
261    !
262    ocean_omp = 'yyyyyy'
[2702]263    CALL getin('OCEAN', ocean_omp)
[1938]264    IF (ocean_omp /= 'yyyyyy') THEN
265       WRITE(lunout,*)'ERROR! Old variable name OCEAN used in parmeter file.'
266       WRITE(lunout,*)'Variable OCEAN has been replaced by the variable type_ocean.'
267       WRITE(lunout,*)'You have to update your parameter file physiq.def to succed running'
[2311]268       CALL abort_physic('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
[2702]269    ENDIF
[1865]270
[2075]271    !Config Key  = t_coupl
272    !Config Desc = Pas de temps du couplage atm/oce en sec.
273    !Config Def  = 86400
274    !Config Help = This is only for testing purpose
[1938]275    !
[2075]276    t_coupl_omp = 86400.
[2702]277    CALL getin('t_coupl', t_coupl_omp)
[2075]278    IF (t_coupl_omp == 0) THEN
279       WRITE(lunout,*)'ERROR! Timestep of coupling between atmosphere and ocean'
280       WRITE(lunout,*)'cannot be zero.'
[2311]281       CALL abort_physic('conf_phys','t_coupl = 0.',1)
[2702]282    ENDIF
[2075]283
284    !
[2114]285    !Config Key  = ok_all_xml
286    !Config Desc = utiliser les xml pourles définitions des champs pour xios
[2702]287    !Config Def  = .FALSE.
[2114]288    !Config Help =
289    !
[2702]290    ok_all_xml_omp = .FALSE.
291    CALL getin('ok_all_xml', ok_all_xml_omp)
[2114]292    !
293
294    !
[1938]295    !Config Key  = VEGET
296    !Config Desc = Type de modele de vegetation
[2702]297    !Config Def  = .FALSE.
[1938]298    !Config Help = Type de modele de vegetation utilise
299    !
300    type_veget_omp ='orchidee'
[2702]301    CALL getin('VEGET', type_veget_omp)
[1938]302    !
[1865]303
[1938]304    ! Martin
305    !Config Key  = ok_snow
306    !Config Desc = Flag to activate snow model SISVAT
[2702]307    !Config Def  = .FALSE.
308    ok_snow_omp = .FALSE.
309    CALL getin('ok_snow', ok_snow_omp)
[1938]310    ! Martin
[1687]311
[1938]312    !Config Key  = OK_journe
313    !Config Desc = Pour des sorties journalieres
[2702]314    !Config Def  = .FALSE.
[1938]315    !Config Help = Pour creer le fichier histday contenant les sorties
316    !              journalieres
317    !
[2702]318    ok_journe_omp = .FALSE.
319    CALL getin('OK_journe', ok_journe_omp)
[1938]320    !
321    !Config Key  = ok_hf
322    !Config Desc = Pour des sorties haute frequence
[2702]323    !Config Def  = .FALSE.
[1938]324    !Config Help = Pour creer le fichier histhf contenant les sorties
325    !              haute frequence ( 3h ou 6h)
326    !
[2702]327    ok_hf_omp = .FALSE.
328    CALL getin('ok_hf', ok_hf_omp)
[1938]329    !
330    !Config Key  = OK_mensuel
331    !Config Desc = Pour des sorties mensuelles
[2702]332    !Config Def  = .TRUE.
[1938]333    !Config Help = Pour creer le fichier histmth contenant les sorties
334    !              mensuelles
335    !
[2702]336    ok_mensuel_omp = .TRUE.
337    CALL getin('OK_mensuel', ok_mensuel_omp)
[1938]338    !
339    !Config Key  = OK_instan
340    !Config Desc = Pour des sorties instantanees
[2702]341    !Config Def  = .FALSE.
[1938]342    !Config Help = Pour creer le fichier histins contenant les sorties
343    !              instantanees
344    !
[2702]345    ok_instan_omp = .FALSE.
346    CALL getin('OK_instan', ok_instan_omp)
[1938]347    !
348    !Config Key  = ok_ade
349    !Config Desc = Aerosol direct effect or not?
[2702]350    !Config Def  = .FALSE.
[1938]351    !Config Help = Used in radlwsw.F
352    !
[2702]353    ok_ade_omp = .FALSE.
354    CALL getin('ok_ade', ok_ade_omp)
[1687]355
[2738]356    !Config Key  = ok_alw
357    !Config Desc = Aerosol longwave effect or not?
358    !Config Def  = .FALSE.
359    !Config Help = Used in radlwsw.F
[1938]360    !
[2738]361    ok_alw_omp = .FALSE.
362    CALL getin('ok_alw', ok_alw_omp)
363
364    !
[1938]365    !Config Key  = ok_aie
366    !Config Desc = Aerosol indirect effect or not?
[2702]367    !Config Def  = .FALSE.
[1938]368    !Config Help = Used in nuage.F and radlwsw.F
369    !
[2702]370    ok_aie_omp = .FALSE.
371    CALL getin('ok_aie', ok_aie_omp)
[1687]372
[1938]373    !
374    !Config Key  = ok_cdnc
375    !Config Desc = ok cloud droplet number concentration
[2702]376    !Config Def  = .FALSE.
[1938]377    !Config Help = Used in newmicro.F
378    !
[2702]379    ok_cdnc_omp = .FALSE.
380    CALL getin('ok_cdnc', ok_cdnc_omp)
[1938]381    !
382    !Config Key  = aerosol_couple
383    !Config Desc = read aerosol in file or calcul by inca
[2702]384    !Config Def  = .FALSE.
[1938]385    !Config Help = Used in physiq.F
386    !
[2702]387    aerosol_couple_omp = .FALSE.
[1938]388    CALL getin('aerosol_couple',aerosol_couple_omp)
389    !
390    !Config Key  = flag_aerosol
391    !Config Desc = which aerosol is use for coupled model
392    !Config Def  = 1
393    !Config Help = Used in physiq.F
394    !
395    ! - flag_aerosol=0 => no aerosol
396    ! - flag_aerosol=1 => so4 only (defaut)
397    ! - flag_aerosol=2 => bc  only
398    ! - flag_aerosol=3 => pom only
399    ! - flag_aerosol=4 => seasalt only
400    ! - flag_aerosol=5 => dust only
401    ! - flag_aerosol=6 => all aerosol
[1687]402
[1938]403    flag_aerosol_omp = 0
404    CALL getin('flag_aerosol',flag_aerosol_omp)
[1687]405
[2644]406    !
407    !Config Key  = flag_bc_internal_mixture
408    !Config Desc = state of mixture for BC aerosols
409    ! - n = external mixture
410    ! - y = internal mixture
411    !Config Def  = n
412    !Config Help = Used in physiq.F / aeropt
413    !
[2702]414    flag_bc_internal_mixture_omp = .FALSE.
[2644]415    CALL getin('flag_bc_internal_mixture',flag_bc_internal_mixture_omp)
416
[1938]417    ! Temporary variable for testing purpose!
418    !Config Key  = new_aod
419    !Config Desc = which calcul of aeropt
[2702]420    !Config Def  = FALSE
[1938]421    !Config Help = Used in physiq.F
422    !
[2702]423    new_aod_omp = .TRUE.
[1938]424    CALL getin('new_aod',new_aod_omp)
[1687]425
[1938]426    !
427    !Config Key  = aer_type
428    !Config Desc = Use a constant field for the aerosols
429    !Config Def  = scenario
430    !Config Help = Used in readaerosol.F90
431    !
432    aer_type_omp = 'scenario'
[2702]433    CALL getin('aer_type', aer_type_omp)
[1687]434
[1938]435    !
436    !Config Key  = bl95_b0
437    !Config Desc = Parameter in CDNC-maer link (Boucher&Lohmann 1995)
[2702]438    !Config Def  = .FALSE.
[1938]439    !Config Help = Used in nuage.F
440    !
441    bl95_b0_omp = 2.
[2702]442    CALL getin('bl95_b0', bl95_b0_omp)
[1687]443
[1938]444    !Config Key  = bl95_b1
445    !Config Desc = Parameter in CDNC-maer link (Boucher&Lohmann 1995)
[2702]446    !Config Def  = .FALSE.
[1938]447    !Config Help = Used in nuage.F
448    !
449    bl95_b1_omp = 0.2
[2702]450    CALL getin('bl95_b1', bl95_b1_omp)
[1687]451
[1938]452    !Config Key  = freq_ISCCP
453    !Config Desc = Frequence d'appel du simulateur ISCCP en secondes;
454    !              par defaut 10800, i.e. 3 heures
455    !Config Def  = 10800.
456    !Config Help = Used in ini_histISCCP.h
457    !
458    freq_ISCCP_omp = 10800.
[2702]459    CALL getin('freq_ISCCP', freq_ISCCP_omp)
[1938]460    !
461    !Config Key  = ecrit_ISCCP
462    !Config Desc = Frequence d'ecriture des resultats du simulateur ISCCP en nombre de jours;
463    !              par defaut 1., i.e. 1 jour
464    !Config Def  = 1.
465    !Config Help = Used in ini_histISCCP.h
466    !
467    !
468    ecrit_ISCCP_omp = 1.
[2702]469    CALL getin('ecrit_ISCCP', ecrit_ISCCP_omp)
[1687]470
[1938]471    !Config Key  = freq_COSP
472    !Config Desc = Frequence d'appel du simulateur COSP en secondes;
473    !              par defaut 10800, i.e. 3 heures
474    !Config Def  = 10800.
475    !Config Help = Used in ini_histdayCOSP.h
476    !
477    freq_COSP_omp = 10800.
[2702]478    CALL getin('freq_COSP', freq_COSP_omp)
[1687]479
[2580]480    !Config Key  = freq_AIRS
481    !Config Desc = Frequence d'appel du simulateur AIRS en secondes;
482    !              par defaut 10800, i.e. 3 heures
483    !Config Def  = 10800.
484    !Config Help = Used in ini_histdayAIRS.h
[1938]485    !
[2580]486    freq_AIRS_omp = 10800.
[2702]487    CALL getin('freq_AIRS', freq_AIRS_omp)
[2580]488
489    !
[1938]490    !Config Key  = ip_ebil_phy
491    !Config Desc = Niveau de sortie pour les diags bilan d'energie
492    !Config Def  = 0
493    !Config Help =
494    !               
495    ip_ebil_phy_omp = 0
[2702]496    CALL getin('ip_ebil_phy', ip_ebil_phy_omp)
[2714]497    IF (ip_ebil_phy_omp/=0) THEN
498       CALL abort_physic('conf_phys','ip_ebil_phy_omp doit etre 0 sur cette version',1)
499    ENDIF
500
[1938]501    !
502    !Config Key  = seuil_inversion
503    !Config Desc = Seuil ur dTh pour le choix entre les schemas de CL
504    !Config Def  = -0.1
505    !Config Help =
506    !               
507    seuil_inversion_omp = -0.1
[2702]508    CALL getin('seuil_inversion', seuil_inversion_omp)
[1687]509
[1938]510    !
511    ! Constante solaire & Parametres orbitaux & taux gaz effet de serre BEG
512    !
513    !Config Key  = R_ecc
514    !Config Desc = Excentricite
515    !Config Def  = 0.016715
516    !Config Help =
517    !               
518    !valeur AMIP II
519    R_ecc_omp = 0.016715
[2702]520    CALL getin('R_ecc', R_ecc_omp)
[1938]521    !
522    !Config Key  = R_peri
523    !Config Desc = Equinoxe
524    !Config Def  =
525    !Config Help =
526    !               
527    !
528    !valeur AMIP II
529    R_peri_omp = 102.7
[2702]530    CALL getin('R_peri', R_peri_omp)
[1938]531    !
532    !Config Key  = R_incl
533    !Config Desc = Inclinaison
534    !Config Def  =
535    !Config Help =
536    !               
537    !
538    !valeur AMIP II
539    R_incl_omp = 23.441
[2702]540    CALL getin('R_incl', R_incl_omp)
[1938]541    !
542    !Config Key  = solaire
543    !Config Desc = Constante solaire en W/m2
544    !Config Def  = 1365.
545    !Config Help =
546    !               
547    !
548    !valeur AMIP II
549    solaire_omp = 1365.
[2702]550    CALL getin('solaire', solaire_omp)
[1938]551    !
552    !Config Key  = co2_ppm
553    !Config Desc = concentration du gaz carbonique en ppmv
554    !Config Def  = 348.
555    !Config Help =
556    !               
557    !
558    !valeur AMIP II
559    co2_ppm_omp = 348.
[2702]560    CALL getin('co2_ppm', co2_ppm_omp)
[1938]561    !
562    !Config Key  = RCO2
563    !Config Desc = Concentration du CO2
564    !Config Def  = co2_ppm * 1.0e-06  * 44.011/28.97
565    !Config Def  = 348. * 1.0e-06  * 44.011/28.97
566    !Config Help =
567    !               
568    ! RCO2 = 5.286789092164308E-04
569    !ancienne valeur
570    RCO2_omp = co2_ppm_omp * 1.0e-06  * 44.011/28.97 ! pour co2_ppm=348.
[1687]571
[2702]572    !  CALL getin('RCO2', RCO2)
[1938]573    !
574    !Config Key  = RCH4
575    !Config Desc = Concentration du CH4
576    !Config Def  = 1.65E-06* 16.043/28.97
577    !Config Help =
578    !               
579    !
580    !valeur AMIP II
581    !OK  RCH4 = 1.65E-06* 16.043/28.97
582    ! RCH4 = 9.137366240938903E-07
583    !
584    !ancienne valeur
585    ! RCH4 = 1.72E-06* 16.043/28.97
[2702]586    !OK CALL getin('RCH4', RCH4)
[1938]587    zzz = 1650.
[2702]588    CALL getin('CH4_ppb', zzz)
[1938]589    CH4_ppb_omp = zzz
590    RCH4_omp = CH4_ppb_omp * 1.0E-09 * 16.043/28.97
591    !
592    !Config Key  = RN2O
593    !Config Desc = Concentration du N2O
594    !Config Def  = 306.E-09* 44.013/28.97
595    !Config Help =
596    !               
597    !
598    !valeur AMIP II
599    !OK  RN2O = 306.E-09* 44.013/28.97
600    ! RN2O = 4.648939592682085E-07
601    !
602    !ancienne valeur
603    ! RN2O = 310.E-09* 44.013/28.97
[2702]604    !OK  CALL getin('RN2O', RN2O)
[1938]605    zzz=306.
[2702]606    CALL getin('N2O_ppb', zzz)
[1938]607    N2O_ppb_omp = zzz
608    RN2O_omp = N2O_ppb_omp * 1.0E-09 * 44.013/28.97
609    !
610    !Config Key  = RCFC11
611    !Config Desc = Concentration du CFC11
612    !Config Def  = 280.E-12* 137.3686/28.97
613    !Config Help =
614    !               
615    !
616    !OK RCFC11 = 280.E-12* 137.3686/28.97
617    zzz = 280.
[2702]618    CALL getin('CFC11_ppt',zzz)
[1938]619    CFC11_ppt_omp = zzz
620    RCFC11_omp=CFC11_ppt_omp* 1.0E-12 * 137.3686/28.97
621    ! RCFC11 = 1.327690990680013E-09
[2702]622    !OK CALL getin('RCFC11', RCFC11)
[1938]623    !
624    !Config Key  = RCFC12
625    !Config Desc = Concentration du CFC12
626    !Config Def  = 484.E-12* 120.9140/28.97
627    !Config Help =
628    !               
629    !
630    !OK RCFC12 = 484.E-12* 120.9140/28.97
631    zzz = 484.
[2702]632    CALL getin('CFC12_ppt',zzz)
[1938]633    CFC12_ppt_omp = zzz
634    RCFC12_omp = CFC12_ppt_omp * 1.0E-12 * 120.9140/28.97
635    ! RCFC12 = 2.020102726958923E-09
[2702]636    !OK CALL getin('RCFC12', RCFC12)
[1687]637
[1938]638    !ajout CFMIP begin
639    !
640    !Config Key  = co2_ppm_per
641    !Config Desc = concentration du co2_ppm_per
642    !Config Def  = 348.
643    !Config Help =
644    !               
645    co2_ppm_per_omp = co2_ppm_omp
[2702]646    CALL getin('co2_ppm_per', co2_ppm_per_omp)
[1938]647    !
648    !Config Key  = RCO2_per
649    !Config Desc = Concentration du CO2_per
650    !Config Def  = co2_ppm_per * 1.0e-06  * 44.011/28.97
651    !Config Def  = 348. * 1.0e-06  * 44.011/28.97
652    !Config Help =
653    !               
654    RCO2_per_omp = co2_ppm_per_omp * 1.0e-06  * 44.011/28.97
[1737]655
[1938]656    !Config Key  = ok_4xCO2atm
657    !Config Desc = Calcul ou non effet radiatif 4xco2
[2702]658    !Config Def  = .FALSE.
[1938]659    !Config Help =
[1737]660
[2702]661    ok_4xCO2atm_omp = .FALSE.
662    CALL getin('ok_4xCO2atm',ok_4xCO2atm_omp)
[1687]663
[1938]664    !Config Key  = RCH4_per
665    !Config Desc = Concentration du CH4_per
666    !Config Def  = 1.65E-06* 16.043/28.97
667    !Config Help =
668    !               
669    zzz = CH4_ppb_omp
[2702]670    CALL getin('CH4_ppb_per', zzz)
[1938]671    CH4_ppb_per_omp = zzz
672    RCH4_per_omp = CH4_ppb_per_omp * 1.0E-09 * 16.043/28.97
673    !
674    !Config Key  = RN2O_per
675    !Config Desc = Concentration du N2O_per
676    !Config Def  = 306.E-09* 44.013/28.97
677    !Config Help =
678    !               
679    zzz = N2O_ppb_omp
[2702]680    CALL getin('N2O_ppb_per', zzz)
[1938]681    N2O_ppb_per_omp = zzz
682    RN2O_per_omp = N2O_ppb_per_omp * 1.0E-09 * 44.013/28.97
683    !
684    !Config Key  = RCFC11_per
685    !Config Desc = Concentration du CFC11_per
686    !Config Def  = 280.E-12* 137.3686/28.97
687    !Config Help =
688    !               
689    zzz = CFC11_ppt_omp
[2702]690    CALL getin('CFC11_ppt_per',zzz)
[1938]691    CFC11_ppt_per_omp = zzz
692    RCFC11_per_omp=CFC11_ppt_per_omp* 1.0E-12 * 137.3686/28.97
693    !
694    !Config Key  = RCFC12_per
695    !Config Desc = Concentration du CFC12_per
696    !Config Def  = 484.E-12* 120.9140/28.97
697    !Config Help =
698    !               
699    zzz = CFC12_ppt_omp
[2702]700    CALL getin('CFC12_ppt_per',zzz)
[1938]701    CFC12_ppt_per_omp = zzz
702    RCFC12_per_omp = CFC12_ppt_per_omp * 1.0E-12 * 120.9140/28.97
703    !ajout CFMIP end
[1687]704
[1938]705    !
706    ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
707    ! Constantes precedemment dans dyn3d/conf_gcm
[1687]708
[1938]709    !Config  Key  = cycle_diurne
710    !Config  Desc = Cycle ddiurne
711    !Config  Def  = y
712    !Config  Help = Cette option permet d'eteidre le cycle diurne.
713    !Config         Peut etre util pour accelerer le code !
714    cycle_diurne_omp = .TRUE.
715    CALL getin('cycle_diurne',cycle_diurne_omp)
[1687]716
[1938]717    !Config  Key  = soil_model
718    !Config  Desc = Modele de sol
719    !Config  Def  = y
720    !Config  Help = Choix du modele de sol (Thermique ?)
721    !Config         Option qui pourait un string afin de pouvoir
722    !Config         plus de choix ! Ou meme une liste d'options !
723    soil_model_omp = .TRUE.
724    CALL getin('soil_model',soil_model_omp)
[1687]725
[1938]726    !Config  Key  = new_oliq
727    !Config  Desc = Nouvelle eau liquide
728    !Config  Def  = y
729    !Config  Help = Permet de mettre en route la
730    !Config         nouvelle parametrisation de l'eau liquide !
731    new_oliq_omp = .TRUE.
732    CALL getin('new_oliq',new_oliq_omp)
[1687]733
[1938]734    !Config  Key  = ok_orodr
735    !Config  Desc = Orodr ???
736    !Config  Def  = y
737    !Config  Help = Y en a pas comprendre !
738    !Config         
739    ok_orodr_omp = .TRUE.
740    CALL getin('ok_orodr',ok_orodr_omp)
[1687]741
[1938]742    !Config  Key  =  ok_orolf
743    !Config  Desc = Orolf ??
744    !Config  Def  = y
745    !Config  Help = Connais pas !
746    ok_orolf_omp = .TRUE.
747    CALL getin('ok_orolf', ok_orolf_omp)
[1687]748
[1938]749    !Config  Key  = ok_limitvrai
750    !Config  Desc = Force la lecture de la bonne annee
751    !Config  Def  = n
752    !Config  Help = On peut forcer le modele a lire le
753    !Config         fichier SST de la bonne annee. C'est une tres bonne
754    !Config         idee, pourquoi ne pas mettre toujours a y ???
755    ok_limitvrai_omp = .FALSE.
756    CALL getin('ok_limitvrai',ok_limitvrai_omp)
[1687]757
[1938]758    !Config  Key  = nbapp_rad
759    !Config  Desc = Frequence d'appel au rayonnement
760    !Config  Def  = 12
761    !Config  Help = Nombre  d'appels des routines de rayonnements
762    !Config         par jour.
763    nbapp_rad_omp = 12
764    CALL getin('nbapp_rad',nbapp_rad_omp)
[1687]765
[1938]766    !Config  Key  = iflag_con
767    !Config  Desc = Flag de convection
768    !Config  Def  = 2
769    !Config  Help = Flag  pour la convection les options suivantes existent :
770    !Config         1 pour LMD,
771    !Config         2 pour Tiedtke,
772    !Config         3 pour CCM(NCAR) 
773    iflag_con_omp = 2
774    CALL getin('iflag_con',iflag_con_omp)
[1753]775
[2707]776    !Config  Key  = nbapp_cv
777    !Config  Desc = Frequence d'appel a la convection
778    !Config  Def  = 0
779    !Config  Help = Nombre  d'appels des routines de convection
780    !Config         par jour. Si =0, appel a chaque pas de temps physique.
781    nbapp_cv_omp = 0
782    CALL getin('nbapp_cv',nbapp_cv_omp)
783
[2730]784    !Config  Key  = nbapp_wk
785    !Config  Desc = Frequence d'appel aux wakes
786    !Config  Def  = 0
787    !Config  Help = Nombre  d'appels des routines de wakes
788    !Config         par jour. Si =0, appel a chaque pas de temps physique.
789    nbapp_wk_omp = 0
790    CALL getin('nbapp_wk',nbapp_wk_omp)
791
[1938]792    !Config  Key  = iflag_ener_conserv
793    !Config  Desc = Flag de convection
794    !Config  Def  = 1
795    !Config  Help = Flag  pour la convection les options suivantes existent :
796    !Config         -1 pour Kinetic energy correction
797    !Config         1  conservation kinetic and enthalpy
798    iflag_ener_conserv_omp = -1
799    CALL getin('iflag_ener_conserv',iflag_ener_conserv_omp)
[1894]800
[2007]801    !Config  Key  = ok_conserv_q
802    !Config  Desc = Switch des corrections de conservation de l'eau
803    !Config  Def  = y
804    !Config  Help = Switch des corrections de conservation de l'eau
805    !Config         y -> corrections activees
806    !Config         n -> conformite avec versions anterieures au 1/4/2014
[2008]807    ok_conserv_q_omp = .FALSE.
[2007]808    CALL getin('ok_conserv_q',ok_conserv_q_omp)
809
[1938]810    !Config  Key  = iflag_fisrtilp_qsat
[2415]811    !Config  Desc = Flag de fisrtilp
812    !Config  Def  = 0
813    !Config  Help = Flag  pour la pluie grande-échelle les options suivantes existent :
814    !Config         >1 nb iterations pour converger dans le calcul de qsat
[1938]815    iflag_fisrtilp_qsat_omp = 0
816    CALL getin('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat_omp)
[1687]817
[2415]818    !Config  Key  = iflag_bergeron
819    !Config  Desc = Flag de fisrtilp
820    !Config  Def  = 0
821    !Config  Help = Flag  pour la pluie grande-échelle les options suivantes existent :
822    !Config         0 pas d effet Bergeron
823    !Config         1 effet Bergeron pour T<0
824    iflag_bergeron_omp = 0
825    CALL getin('iflag_bergeron',iflag_bergeron_omp)
826
[1938]827    !
828    !
829    !
830    ! Constante solaire & Parametres orbitaux & taux gaz effet de serre END
831    !
832    ! KE
833    !
[1687]834
[2253]835    !Config key  = cvl_comp_threshold
836    !Config Desc = maximum fraction of convective points enabling compression
837    !Config Def  = 1.00
838    !Config Help = fields are compressed when less than a fraction cvl_comp_threshold
839    !Config Help = of the points is convective.
840    cvl_comp_threshold_omp = 1.00
841    CALL getin('cvl_comp_threshold', cvl_comp_threshold_omp)
842
843    !Config key  = cvl_sig2feed
844    !Config Desc = sigma coordinate at top of feeding layer
845    !Config Def  = 0.97
846    !Config Help = deep convection is fed by the layer extending from the surface (pressure ps)
847    !Config Help = and cvl_sig2feed*ps.
848    cvl_sig2feed_omp = 0.97
849    CALL getin('cvl_sig2feed', cvl_sig2feed_omp)
850
[1938]851    !Config key  = cvl_corr
852    !Config Desc = Facteur multiplication des precip convectives dans KE
853    !Config Def  = 1.00
854    !Config Help = 1.02 pour un moderne ou un pre-ind. A ajuster pour un glaciaire
855    cvl_corr_omp = 1.00
856    CALL getin('cvl_corr', cvl_corr_omp)
[1687]857
858
[1938]859    !Config Key  = epmax
860    !Config Desc = Efficacite precip
861    !Config Def  = 0.993
862    !Config Help =
863    !
864    epmax_omp = .993
[2702]865    CALL getin('epmax', epmax_omp)
[2481]866
867    coef_epmax_cape_omp = 0.0   
[2702]868    CALL getin('coef_epmax_cape', coef_epmax_cape_omp)       
[1938]869    !
870    !Config Key  = ok_adj_ema
871    !Config Desc = 
[2702]872    !Config Def  = FALSE
[1938]873    !Config Help =
874    !
[2702]875    ok_adj_ema_omp = .FALSE.
876    CALL getin('ok_adj_ema',ok_adj_ema_omp)
[1938]877    !
878    !Config Key  = iflag_clw
879    !Config Desc = 
880    !Config Def  = 0
881    !Config Help =
882    !
883    iflag_clw_omp = 0
[2702]884    CALL getin('iflag_clw',iflag_clw_omp)
[1938]885    !
886    !Config Key  = cld_lc_lsc
887    !Config Desc = 
888    !Config Def  = 2.6e-4
889    !Config Help =
890    !
891    cld_lc_lsc_omp = 2.6e-4
[2702]892    CALL getin('cld_lc_lsc',cld_lc_lsc_omp)
[1938]893    !
894    !Config Key  = cld_lc_con
895    !Config Desc = 
896    !Config Def  = 2.6e-4
897    !Config Help =
898    !
899    cld_lc_con_omp = 2.6e-4
[2702]900    CALL getin('cld_lc_con',cld_lc_con_omp)
[1938]901    !
902    !Config Key  = cld_tau_lsc
903    !Config Desc = 
904    !Config Def  = 3600.
905    !Config Help =
906    !
907    cld_tau_lsc_omp = 3600.
[2702]908    CALL getin('cld_tau_lsc',cld_tau_lsc_omp)
[1938]909    !
910    !Config Key  = cld_tau_con
911    !Config Desc = 
912    !Config Def  = 3600.
913    !Config Help =
914    !
915    cld_tau_con_omp = 3600.
[2702]916    CALL getin('cld_tau_con',cld_tau_con_omp)
[1938]917    !
918    !Config Key  = ffallv_lsc
919    !Config Desc = 
920    !Config Def  = 1.
921    !Config Help =
922    !
923    ffallv_lsc_omp = 1.
[2702]924    CALL getin('ffallv_lsc',ffallv_lsc_omp)
[1938]925    !
926    !Config Key  = ffallv_con
927    !Config Desc = 
928    !Config Def  = 1.
929    !Config Help =
930    !
931    ffallv_con_omp = 1.
[2702]932    CALL getin('ffallv_con',ffallv_con_omp)
[1938]933    !
934    !Config Key  = coef_eva
935    !Config Desc = 
936    !Config Def  = 2.e-5
937    !Config Help =
938    !
939    coef_eva_omp = 2.e-5
[2702]940    CALL getin('coef_eva',coef_eva_omp)
[1938]941    !
942    !Config Key  = reevap_ice
943    !Config Desc = 
[2702]944    !Config Def  = .FALSE.
[1938]945    !Config Help =
946    !
[2702]947    reevap_ice_omp = .FALSE.
948    CALL getin('reevap_ice',reevap_ice_omp)
[1687]949
[1938]950    !Config Key  = iflag_ratqs
951    !Config Desc =
952    !Config Def  = 1
953    !Config Help =
954    !
955    iflag_ratqs_omp = 1
[2702]956    CALL getin('iflag_ratqs',iflag_ratqs_omp)
[1687]957
[1938]958    !
959    !Config Key  = iflag_radia
960    !Config Desc = 
961    !Config Def  = 1
962    !Config Help =
963    !
964    iflag_radia_omp = 1
[2702]965    CALL getin('iflag_radia',iflag_radia_omp)
[1687]966
[1938]967    !
968    !Config Key  = iflag_rrtm
969    !Config Desc = 
970    !Config Def  = 0
971    !Config Help =
972    !
973    iflag_rrtm_omp = 0
[2702]974    CALL getin('iflag_rrtm',iflag_rrtm_omp)
[1687]975
[1938]976    !
[1989]977    !Config Key  = NSW
978    !Config Desc = 
979    !Config Def  = 0
980    !Config Help =
981    !
[2413]982    NSW_omp = 2
[2702]983    CALL getin('NSW',NSW_omp)
[2357]984    !albedo SB >>>
[2227]985    iflag_albedo_omp = 0
[2702]986    CALL getin('iflag_albedo',iflag_albedo_omp)
[1989]987
[2702]988    ok_chlorophyll_omp=.FALSE.
989    CALL getin('ok_chlorophyll',ok_chlorophyll_omp)
[2357]990    !albedo SB <<<
[2785]991    !
992    !Config Key  = ok_sun_time
993    !Config Desc = oui ou non variabilite solaire
994    !Config Def  = .FALSE.
995    !Config Help =
996    !
997    !
998    !valeur AMIP II
999    ok_suntime_rrtm_omp = .FALSE.
1000    IF (iflag_rrtm_omp==1) THEN
1001      CALL getin('ok_suntime_rrtm',ok_suntime_rrtm_omp)
1002    ENDIF
1003    !
1004    !Config Key  = flag_aerosol_strat
1005    !Config Desc = use stratospheric aerosols 0, 1, 2
1006    ! - 0 = no stratospheric aerosols
1007    ! - 1 = stratospheric aerosols scaled from 550 nm AOD
1008    ! - 2 = stratospheric aerosol properties from CMIP6
1009    !Config Def  = 0
1010    !Config Help = Used in physiq.F
1011    !
1012    !
1013    flag_aerosol_strat_omp = 0
1014    IF (iflag_rrtm_omp==1) THEN
1015      CALL getin('flag_aerosol_strat',flag_aerosol_strat_omp)
1016    ENDIF
[2227]1017
[1989]1018    !
[2236]1019    !Config Key  = iflag_cld_th
[1938]1020    !Config Desc = 
1021    !Config Def  = 1
1022    !Config Help =
1023    !
[2236]1024    iflag_cld_th_omp = 1
[2357]1025    ! On lit deux fois avec l'ancien et le nouveau nom
1026    ! pour assurer une retrocompatiblite.
1027    ! A abandonner un jour
[2702]1028    CALL getin('iflag_cldcon',iflag_cld_th_omp)
1029    CALL getin('iflag_cld_th',iflag_cld_th_omp)
[2236]1030    iflag_cld_cv_omp = 0
[2702]1031    CALL getin('iflag_cld_cv',iflag_cld_cv_omp)
[2205]1032
1033    !
1034    !Config Key  = tau_cld_cv
1035    !Config Desc =
1036    !Config Def  = 10.
1037    !Config Help =
1038    !
1039    tau_cld_cv_omp = 10.
[2702]1040    CALL getin('tau_cld_cv',tau_cld_cv_omp)
[2205]1041
1042    !
1043    !Config Key  = coefw_cld_cv
1044    !Config Desc =
1045    !Config Def  = 0.1
1046    !Config Help =
1047    !
1048    coefw_cld_cv_omp = 0.1
[2702]1049    CALL getin('coefw_cld_cv',coefw_cld_cv_omp)
[2205]1050
1051
1052
1053
1054    !
[1938]1055    !Config Key  = iflag_pdf
1056    !Config Desc = 
1057    !Config Def  = 0
1058    !Config Help =
1059    !
1060    iflag_pdf_omp = 0
[2702]1061    CALL getin('iflag_pdf',iflag_pdf_omp)
[1938]1062    !
1063    !Config Key  = fact_cldcon
1064    !Config Desc = 
1065    !Config Def  = 0.375
1066    !Config Help =
1067    !
1068    fact_cldcon_omp = 0.375
[2702]1069    CALL getin('fact_cldcon',fact_cldcon_omp)
[1687]1070
[1938]1071    !
1072    !Config Key  = facttemps
1073    !Config Desc = 
1074    !Config Def  = 1.e-4
1075    !Config Help =
1076    !
1077    facttemps_omp = 1.e-4
[2702]1078    CALL getin('facttemps',facttemps_omp)
[1687]1079
[1938]1080    !
1081    !Config Key  = ok_newmicro
1082    !Config Desc = 
[2702]1083    !Config Def  = .TRUE.
[1938]1084    !Config Help =
1085    !
[2702]1086    ok_newmicro_omp = .TRUE.
1087    CALL getin('ok_newmicro',ok_newmicro_omp)
[1938]1088    !
1089    !Config Key  = ratqsbas
1090    !Config Desc = 
1091    !Config Def  = 0.01
1092    !Config Help =
1093    !
1094    ratqsbas_omp = 0.01
[2702]1095    CALL getin('ratqsbas',ratqsbas_omp)
[1938]1096    !
1097    !Config Key  = ratqshaut
1098    !Config Desc = 
1099    !Config Def  = 0.3
1100    !Config Help =
1101    !
1102    ratqshaut_omp = 0.3
[2702]1103    CALL getin('ratqshaut',ratqshaut_omp)
[1687]1104
[1938]1105    !Config Key  = tau_ratqs
1106    !Config Desc = 
1107    !Config Def  = 1800.
1108    !Config Help =
1109    !
1110    tau_ratqs_omp = 1800.
[2702]1111    CALL getin('tau_ratqs',tau_ratqs_omp)
[1687]1112
[1938]1113    !
1114    !-----------------------------------------------------------------------
1115    ! Longitude solaire pour le calcul de l'ensoleillement en degre
1116    ! si on veut imposer la saison. Sinon, solarlong0=-999.999
1117    !Config Key  = solarlong0
1118    !Config Desc = 
1119    !Config Def  = -999.999
1120    !Config Help =
1121    !
1122    solarlong0_omp = -999.999
[2702]1123    CALL getin('solarlong0',solarlong0_omp)
[1938]1124    !
1125    !-----------------------------------------------------------------------
1126    !  Valeur imposee pour configuration idealisees
1127    !Config Key  = qsol0 pour le bucket, evap0 pour aquaplanetes, albsno0
1128    ! Default value -1 to activate the full computation
1129    qsol0_omp = -1.
[2702]1130    CALL getin('qsol0',qsol0_omp)
[1938]1131    evap0_omp = -1.
[2702]1132    CALL getin('evap0',evap0_omp)
[1938]1133    albsno0_omp = -1.
[2702]1134    CALL getin('albsno0',albsno0_omp)
[1938]1135    !
1136    !-----------------------------------------------------------------------
1137    !
[2915]1138    !Config Key  = iflag_sic
[1938]1139    !Config Desc = 
[2915]1140    !Config Def  = 0
1141    !Config Help =
1142    !
1143    iflag_sic_omp = 0
1144    CALL getin('iflag_sic',iflag_sic_omp)
1145    !
1146    !Config Key  = inertie_sic
1147    !Config Desc = 
[1938]1148    !Config Def  = 2000.
1149    !Config Help =
1150    !
[2915]1151    inertie_sic_omp = 2000.
1152    CALL getin('inertie_sic',inertie_sic_omp)
[1938]1153    !
[2915]1154    !Config Key  = inertie_lic
1155    !Config Desc = 
1156    !Config Def  = 2000.
1157    !Config Help =
1158    !
1159    inertie_lic_omp = 2000.
1160    CALL getin('inertie_lic',inertie_lic_omp)
1161    !
[1938]1162    !Config Key  = inertie_sno
1163    !Config Desc = 
1164    !Config Def  = 2000.
1165    !Config Help =
1166    !
1167    inertie_sno_omp = 2000.
[2702]1168    CALL getin('inertie_sno',inertie_sno_omp)
[1938]1169    !
1170    !Config Key  = inertie_sol
1171    !Config Desc = 
1172    !Config Def  = 2000.
1173    !Config Help =
1174    !
1175    inertie_sol_omp = 2000.
[2702]1176    CALL getin('inertie_sol',inertie_sol_omp)
[1687]1177
[1938]1178    !
1179    !Config Key  = rad_froid
1180    !Config Desc = 
1181    !Config Def  = 35.0
1182    !Config Help =
1183    !
1184    rad_froid_omp = 35.0
[2702]1185    CALL getin('rad_froid',rad_froid_omp)
[1687]1186
[1938]1187    !
1188    !Config Key  = rad_chau1
1189    !Config Desc = 
1190    !Config Def  = 13.0
1191    !Config Help =
1192    !
1193    rad_chau1_omp = 13.0
[2702]1194    CALL getin('rad_chau1',rad_chau1_omp)
[1687]1195
[1938]1196    !
1197    !Config Key  = rad_chau2
1198    !Config Desc = 
1199    !Config Def  = 9.0
1200    !Config Help =
1201    !
1202    rad_chau2_omp = 9.0
[2702]1203    CALL getin('rad_chau2',rad_chau2_omp)
[1687]1204
[1938]1205    !
1206    !Config Key  = t_glace_min
1207    !Config Desc = 
1208    !Config Def  = 258.
1209    !Config Help =
1210    !
1211    t_glace_min_omp = 258.
[2702]1212    CALL getin('t_glace_min',t_glace_min_omp)
[1687]1213
[1938]1214    !
1215    !Config Key  = t_glace_max
1216    !Config Desc = 
1217    !Config Def  = 273.13
1218    !Config Help =
1219    !
1220    t_glace_max_omp = 273.13
[2702]1221    CALL getin('t_glace_max',t_glace_max_omp)
[1849]1222
[1938]1223    !
[2006]1224    !Config Key  = exposant_glace
1225    !Config Desc = 
1226    !Config Def  = 2.
1227    !Config Help =
1228    !
1229    exposant_glace_omp = 1.
[2702]1230    CALL getin('exposant_glace',exposant_glace_omp)
[2006]1231
1232    !
1233    !Config Key  = iflag_t_glace
1234    !Config Desc = 
1235    !Config Def  = 0
1236    !Config Help =
1237    !
1238    iflag_t_glace_omp = 0
[2702]1239    CALL getin('iflag_t_glace',iflag_t_glace_omp)
[2006]1240
1241    !
[2547]1242    !Config Key  = iflag_cloudth_vert
1243    !Config Desc = 
1244    !Config Def  = 0
1245    !Config Help =
1246    !
1247    iflag_cloudth_vert_omp = 0
[2702]1248    CALL getin('iflag_cloudth_vert',iflag_cloudth_vert_omp)
[2547]1249
1250    !
[2945]1251    !Config Key  = iflag_rain_incloud_vol
1252    !Config Desc = 
1253    !Config Def  = 0
1254    !Config Help =
1255    !
1256    iflag_rain_incloud_vol_omp = 0
1257    CALL getin('iflag_rain_incloud_vol',iflag_rain_incloud_vol_omp)
1258
1259    !
[1938]1260    !Config Key  = iflag_ice_thermo
1261    !Config Desc = 
1262    !Config Def  = 0
1263    !Config Help =
1264    !
1265    iflag_ice_thermo_omp = 0
[2702]1266    CALL getin('iflag_ice_thermo',iflag_ice_thermo_omp)
[1687]1267
[1938]1268    !Config Key  = rei_min
1269    !Config Desc = 
1270    !Config Def  = 3.5
1271    !Config Help =
1272    !
1273    rei_min_omp = 3.5
[2702]1274    CALL getin('rei_min',rei_min_omp)
[1687]1275
[1938]1276    !
1277    !Config Key  = rei_max
1278    !Config Desc = 
1279    !Config Def  = 61.29
1280    !Config Help =
1281    !
1282    rei_max_omp = 61.29
[2702]1283    CALL getin('rei_max',rei_max_omp)
[1687]1284
[1938]1285    !
1286    !Config Key  = top_height
1287    !Config Desc =
1288    !Config Def  = 3
1289    !Config Help =
1290    !
1291    top_height_omp = 3
[2702]1292    CALL getin('top_height',top_height_omp)
[1687]1293
[1938]1294    !
1295    !Config Key  = overlap
1296    !Config Desc =
1297    !Config Def  = 3
1298    !Config Help =
1299    !
1300    overlap_omp = 3
[2702]1301    CALL getin('overlap',overlap_omp)
[1687]1302
[1938]1303    !
1304    !Config Key  = cdmmax
1305    !Config Desc =
1306    !Config Def  = 1.3E-3
1307    !Config Help =
1308    !
1309    cdmmax_omp = 1.3E-3
[2702]1310    CALL getin('cdmmax',cdmmax_omp)
[1687]1311
[1938]1312    !
1313    !Config Key  = cdhmax
1314    !Config Desc =
1315    !Config Def  = 1.1E-3
1316    !Config Help =
1317    !
1318    cdhmax_omp = 1.1E-3
[2702]1319    CALL getin('cdhmax',cdhmax_omp)
[1687]1320
[1938]1321    !261103
1322    !
1323    !Config Key  = ksta
1324    !Config Desc =
1325    !Config Def  = 1.0e-10
1326    !Config Help =
1327    !
1328    ksta_omp = 1.0e-10
[2702]1329    CALL getin('ksta',ksta_omp)
[1687]1330
[1938]1331    !
1332    !Config Key  = ksta_ter
1333    !Config Desc =
1334    !Config Def  = 1.0e-10
1335    !Config Help =
1336    !
1337    ksta_ter_omp = 1.0e-10
[2702]1338    CALL getin('ksta_ter',ksta_ter_omp)
[1687]1339
[2126]1340    !Config Key  = f_ri_cd_min
1341    !Config Desc =
1342    !Config Def  = 0.1
1343    !Config Help =
[1938]1344    !
[2126]1345    f_ri_cd_min_omp = 0.1
[2702]1346    CALL getin('f_ri_cd_min',f_ri_cd_min_omp)
[2126]1347
1348    !
[1938]1349    !Config Key  = ok_kzmin
1350    !Config Desc =
[2702]1351    !Config Def  = .TRUE.
[1938]1352    !Config Help =
1353    !
[2702]1354    ok_kzmin_omp = .TRUE.
1355    CALL getin('ok_kzmin',ok_kzmin_omp)
[1687]1356
[2561]1357    pbl_lmixmin_alpha_omp=0.0
[2702]1358    CALL getin('pbl_lmixmin_alpha',pbl_lmixmin_alpha_omp)
[2561]1359
[1938]1360    !
1361    !Config Key  = fmagic
1362    !Config Desc = additionnal multiplicator factor used for albedo
1363    !Config Def  = 1.
1364    !Config Help = additionnal multiplicator factor used in albedo.F
1365    !
1366    fmagic_omp = 1.
[2702]1367    CALL getin('fmagic',fmagic_omp)
[1687]1368
[1938]1369    !
1370    !Config Key  = pmagic
1371    !Config Desc = additional factor used for albedo
1372    !Config Def  = 0.
1373    !Config Help = additional factor used in albedo.F
1374    !
1375    pmagic_omp = 0.
[2702]1376    CALL getin('pmagic',pmagic_omp)
[1687]1377
1378
[1938]1379    !Config Key = ok_lic_melt
1380    !Config Desc = Prise en compte de la fonte de la calotte dans le bilan d'eau
[2702]1381    !Config Def  = .FALSE.
1382    !Config Help = mettre a .FALSE. pour assurer la conservation en eau
1383    ok_lic_melt_omp = .FALSE.
1384    CALL getin('ok_lic_melt', ok_lic_melt_omp)
[1687]1385
[1938]1386    !
1387    ! PARAMETER FOR THE PLANETARY BOUNDARY LAYER
1388    !
[1687]1389
[1938]1390    !Config Key  = iflag_pbl
1391    !Config Desc =
1392    !Config Def  = 1
1393    !Config Help =
1394    !
1395    iflag_pbl_omp = 1
[2702]1396    CALL getin('iflag_pbl',iflag_pbl_omp)
[1938]1397    !
[2159]1398    !Config Key  = iflag_pbl_split
[2852]1399    !Config Desc = decimal flag: least signif digit = split vdf; next digit = split thermals
[2159]1400    !Config Def  = 0
[2852]1401    !Config Help = 0-> no splitting; 1-> vdf splitting; 10-> thermals splitting; 11-> full splitting
[2159]1402    !
1403    iflag_pbl_split_omp = 0
[2852]1404    call getin('iflag_pbl_split',iflag_pbl_split_omp)
[2159]1405    !
[2455]1406    !Config Key  = iflag_order2_sollw
1407    !Config Desc =
1408    !Config Def  = 0
1409    !Config Help =
1410    !
1411    iflag_order2_sollw_omp = 0
[2702]1412    CALL getin('iflag_order2_sollw',iflag_order2_sollw_omp)
[2455]1413    !
[1938]1414    !Config Key  = iflag_thermals
1415    !Config Desc =
1416    !Config Def  = 0
1417    !Config Help =
1418    !
1419    iflag_thermals_omp = 0
[2702]1420    CALL getin('iflag_thermals',iflag_thermals_omp)
[1938]1421    !
[2000]1422    !Config Key  = iflag_thermals_ed
1423    !Config Desc =
1424    !Config Def  = 0
1425    !Config Help =
[1938]1426    !
[2000]1427    fact_thermals_ed_dz_omp = 0.1
1428
[2702]1429    CALL getin('fact_thermals_ed_dz',fact_thermals_ed_dz_omp)
[2000]1430    !
1431    !
[1938]1432    !Config Key  = iflag_thermals_ed
1433    !Config Desc =
1434    !Config Def  = 0
1435    !Config Help =
1436    !
1437    iflag_thermals_ed_omp = 0
[2702]1438    CALL getin('iflag_thermals_ed',iflag_thermals_ed_omp)
[1938]1439    !
1440    !
1441    !Config Key  = iflag_thermals_optflux
1442    !Config Desc =
1443    !Config Def  = 0
1444    !Config Help =
1445    !
1446    iflag_thermals_optflux_omp = 0
[2702]1447    CALL getin('iflag_thermals_optflux',iflag_thermals_optflux_omp)
[1938]1448    !
[1998]1449    !Config Key  = iflag_thermals_closure
1450    !Config Desc =
1451    !Config Def  = 0
1452    !Config Help =
[1938]1453    !
[1998]1454    iflag_thermals_closure_omp = 1
[2702]1455    CALL getin('iflag_thermals_closure',iflag_thermals_closure_omp)
[1998]1456    !
[1938]1457    !Config Key  = nsplit_thermals
1458    !Config Desc =
1459    !Config Def  = 1
1460    !Config Help =
1461    !
1462    nsplit_thermals_omp = 1
[2702]1463    CALL getin('nsplit_thermals',nsplit_thermals_omp)
[1687]1464
[1938]1465    !Config Key  = alp_bl_k
1466    !Config Desc =
1467    !Config Def  = 0.
1468    !Config Help =
1469    !
1470    alp_bl_k_omp = 1.
[2702]1471    CALL getin('alp_bl_k',alp_bl_k_omp)
[1687]1472
[1938]1473    ! nrlmd le 10/04/2012
[1687]1474
[1938]1475    !Config Key  = iflag_trig_bl
1476    !Config Desc = 
1477    !Config Def  = 0
1478    !Config Help =
1479    !
1480    iflag_trig_bl_omp = 0
[2702]1481    CALL getin('iflag_trig_bl',iflag_trig_bl_omp)
[1687]1482
[1938]1483    !Config Key  = s_trig_bl
1484    !Config Desc = 
1485    !Config Def  = 0
1486    !Config Help =
1487    !
1488    s_trig_omp = 2e7
[2702]1489    CALL getin('s_trig',s_trig_omp)
[1687]1490
[1938]1491    !Config Key  = tau_trig_shallow
1492    !Config Desc = 
1493    !Config Def  = 0
1494    !Config Help =
1495    !
1496    tau_trig_shallow_omp = 600
[2702]1497    CALL getin('tau_trig_shallow',tau_trig_shallow_omp)
[1687]1498
[1938]1499    !Config Key  = tau_trig_deep
1500    !Config Desc = 
1501    !Config Def  = 0
1502    !Config Help =
1503    !
1504    tau_trig_deep_omp = 1800
[2702]1505    CALL getin('tau_trig_deep',tau_trig_deep_omp)
[1687]1506
[1938]1507    !Config Key  = iflag_clos_bl
1508    !Config Desc = 
1509    !Config Def  = 0
1510    !Config Help =
1511    !
1512    iflag_clos_bl_omp = 0
[2702]1513    CALL getin('iflag_clos_bl',iflag_clos_bl_omp)
[1687]1514
[1938]1515    ! fin nrlmd le 10/04/2012
[1687]1516
[1938]1517    !
1518    !Config Key  = tau_thermals
1519    !Config Desc =
1520    !Config Def  = 0.
1521    !Config Help =
1522    !
1523    tau_thermals_omp = 0.
[2702]1524    CALL getin('tau_thermals',tau_thermals_omp)
[1687]1525
[1938]1526    !
1527    !Config Key  = iflag_coupl
1528    !Config Desc =
1529    !Config Def  = 0
1530    !Config Help =
1531    !
1532    iflag_coupl_omp = 0
[2702]1533    CALL getin('iflag_coupl',iflag_coupl_omp)
[1687]1534
[1938]1535    !
1536    !Config Key  = iflag_clos
1537    !Config Desc = 
1538    !Config Def  = 0
1539    !Config Help =
1540    !
1541    iflag_clos_omp = 1
[2702]1542    CALL getin('iflag_clos',iflag_clos_omp)
[1938]1543    !
[2201]1544    !Config Key  = coef_clos_ls
1545    !Config Desc = 
1546    !Config Def  = 0
1547    !Config Help =
1548    !
1549    coef_clos_ls_omp = 0.
[2702]1550    CALL getin('coef_clos_ls',coef_clos_ls_omp)
[2201]1551
1552    !
[1938]1553    !Config Key  = iflag_cvl_sigd
1554    !Config Desc = 
1555    !Config Def  = 0
1556    !Config Help =
1557    !
1558    iflag_cvl_sigd_omp = 0
[2702]1559    CALL getin('iflag_cvl_sigd',iflag_cvl_sigd_omp)
[1687]1560
[1938]1561    !Config Key  = iflag_wake
1562    !Config Desc = 
1563    !Config Def  = 0
1564    !Config Help =
1565    !
1566    iflag_wake_omp = 0
[2702]1567    CALL getin('iflag_wake',iflag_wake_omp)
[1687]1568
[1938]1569    !Config Key  = alp_offset
1570    !Config Desc = 
1571    !Config Def  = 0
1572    !Config Help =
1573    !
1574    alp_offset_omp = 0.
[2702]1575    CALL getin('alp_offset',alp_offset_omp)
[1687]1576
[1938]1577    !
1578    !Config Key  = lev_histhf
1579    !Config Desc =
1580    !Config Def  = 1
1581    !Config Help =
1582    !
1583    lev_histhf_omp = 1
[2702]1584    CALL getin('lev_histhf',lev_histhf_omp)
[1687]1585
[1938]1586    !
1587    !Config Key  = lev_histday
1588    !Config Desc =
1589    !Config Def  = 1
1590    !Config Help =
1591    !
1592    lev_histday_omp = 1
[2702]1593    CALL getin('lev_histday',lev_histday_omp)
[1687]1594
[1938]1595    !
1596    !Config Key  = lev_histmth
1597    !Config Desc =
1598    !Config Def  = 2
1599    !Config Help =
1600    !
1601    lev_histmth_omp = 2
[2702]1602    CALL getin('lev_histmth',lev_histmth_omp)
[1938]1603    !
1604    !Config Key  = lev_histins
1605    !Config Desc =
1606    !Config Def  = 1
1607    !Config Help =
1608    !
1609    lev_histins_omp = 1
[2702]1610    CALL getin('lev_histins',lev_histins_omp)
[1938]1611    !
1612    !Config Key  = lev_histLES
1613    !Config Desc =
1614    !Config Def  = 1
1615    !Config Help =
1616    !
1617    lev_histLES_omp = 1
[2702]1618    CALL getin('lev_histLES',lev_histLES_omp)
[1938]1619    !
1620    !Config Key  = lev_histdayNMC
1621    !Config Desc =
1622    !Config Def  = 8
1623    !Config Help =
1624    !
1625    lev_histdayNMC_omp = 8
[2702]1626    CALL getin('lev_histdayNMC',lev_histdayNMC_omp)
[1938]1627    !
1628    !Config Key  = levout_histNMC
1629    !Config Desc =
1630    !Config Def  = 5
1631    !Config Help =
1632    !
1633    levout_histNMC_omp(1) = 5
1634    levout_histNMC_omp(2) = 5
1635    levout_histNMC_omp(3) = 5
[2702]1636    CALL getin('levout_histNMC',levout_histNMC_omp)
[1938]1637    !
1638    !histNMC BEG
1639    !Config Key  = ok_histNMC
1640    !Config Desc = ok_histNMC(1) = frequence de sortie fichiers histmthNMC
1641    !Config Desc = ok_histNMC(2) = frequence de sortie fichiers histdayNMC
1642    !Config Desc = ok_histNMC(3) = frequence de sortie fichiers histhfNMC
1643    !Config Def  = n, n, n
1644    !Config Help =
1645    !
[2702]1646    ok_histNMC_omp(1) = .FALSE.
1647    ok_histNMC_omp(2) = .FALSE.
1648    ok_histNMC_omp(3) = .FALSE.
1649    CALL getin('ok_histNMC',ok_histNMC_omp)
[1938]1650    !
1651    !Config Key  = freq_outNMC
1652    !Config Desc = freq_outNMC(1) = frequence de sortie fichiers histmthNMC
1653    !Config Desc = freq_outNMC(2) = frequence de sortie fichiers histdayNMC
1654    !Config Desc = freq_outNMC(3) = frequence de sortie fichiers histhfNMC
1655    !Config Def  = 2592000., 86400., 21600. (1mois, 1jour, 6h)
1656    !Config Help =
1657    !
1658    freq_outNMC_omp(1) = mth_len
1659    freq_outNMC_omp(2) = 1.
1660    freq_outNMC_omp(3) = 1./4.
[2702]1661    CALL getin('freq_outNMC',freq_outNMC_omp)
[1938]1662    !
1663    !Config Key  = freq_calNMC
1664    !Config Desc = freq_calNMC(1) = frequence de calcul fichiers histmthNMC
1665    !Config Desc = freq_calNMC(2) = frequence de calcul fichiers histdayNMC
1666    !Config Desc = freq_calNMC(3) = frequence de calcul fichiers histhfNMC
1667    !Config Def  = pasphys
1668    !Config Help =
1669    !
1670    freq_calNMC_omp(1) = pasphys
1671    freq_calNMC_omp(2) = pasphys
1672    freq_calNMC_omp(3) = pasphys
[2702]1673    CALL getin('freq_calNMC',freq_calNMC_omp)
[1938]1674    !
1675    !Config Key  = type_run
1676    !Config Desc =
1677    !Config Def  = 'AMIP'/'CFMIP'  ou 'CLIM'/'ENSP'
1678    !Config Help =
1679    !
1680    type_run_omp = 'AMIP'
[2702]1681    CALL getin('type_run',type_run_omp)
[1687]1682
[1938]1683    !
1684    !Config Key  = ok_cosp
1685    !Config Desc =
[2702]1686    !Config Def  = .FALSE.
[1938]1687    !Config Help =
1688    !
[2702]1689    ok_cosp_omp = .FALSE.
1690    CALL getin('ok_cosp',ok_cosp_omp)
[1687]1691
[1938]1692    !
[2580]1693    !Config Key  = ok_airs
1694    !Config Desc =
[2702]1695    !Config Def  = .FALSE.
[2580]1696    !Config Help =
1697    !
[2702]1698    ok_airs_omp = .FALSE.
1699    CALL getin('ok_airs',ok_airs_omp)
[2580]1700
1701    !
[1938]1702    !Config Key  = ok_mensuelCOSP
1703    !Config Desc =
[2702]1704    !Config Def  = .TRUE.
[1938]1705    !Config Help =
1706    !
[2702]1707    ok_mensuelCOSP_omp = .TRUE.
1708    CALL getin('ok_mensuelCOSP',ok_mensuelCOSP_omp)
[1687]1709
[1938]1710    !
1711    !Config Key  = ok_journeCOSP
1712    !Config Desc =
[2702]1713    !Config Def  = .TRUE.
[1938]1714    !Config Help =
1715    !
[2702]1716    ok_journeCOSP_omp = .TRUE.
1717    CALL getin('ok_journeCOSP',ok_journeCOSP_omp)
[1687]1718
[1938]1719    !
1720    !Config Key  = ok_hfCOSP
1721    !Config Desc =
[2702]1722    !Config Def  = .FALSE.
[1938]1723    !Config Help =
1724    !
[2702]1725    ok_hfCOSP_omp = .FALSE.
1726    CALL getin('ok_hfCOSP',ok_hfCOSP_omp)
[1687]1727
[1938]1728    !
1729    ! coordonnees (lonmin_ins, lonmax_ins, latmin_ins, latmax_ins) pour la zone
1730    ! avec sorties instantannees tous les pas de temps de la physique => "histbilKP_ins.nc"
1731    !
1732    !Config Key  = lonmin_ins
1733    !Config Desc = 100. 
1734    !Config Def  = longitude minimale sorties "bilKP_ins"
1735    !Config Help =
1736    !
1737    lonmin_ins_omp = 100.
[2702]1738    CALL getin('lonmin_ins',lonmin_ins_omp)
[1938]1739    !
1740    !Config Key  = lonmax_ins
1741    !Config Desc = 130.
1742    !Config Def  = longitude maximale sorties "bilKP_ins"
1743    !Config Help =
1744    !
1745    lonmax_ins_omp = 130.
[2702]1746    CALL getin('lonmax_ins',lonmax_ins_omp)
[1938]1747    !
1748    !Config Key  = latmin_ins
1749    !Config Desc = -20. 
1750    !Config Def  = latitude minimale sorties "bilKP_ins"
1751    !Config Help =
1752    !
1753    latmin_ins_omp = -20.
[2702]1754    CALL getin('latmin_ins',latmin_ins_omp)
[1938]1755    !
1756    !Config Key  = latmax_ins
1757    !Config Desc = 20.
1758    !Config Def  = latitude maximale sorties "bilKP_ins"
1759    !Config Help =
1760    !
1761    latmax_ins_omp = 20.
[2702]1762    CALL getin('latmax_ins',latmax_ins_omp)
[1938]1763    !
1764    !Config Key  = ecrit_hf
1765    !Config Desc =
1766    !Config Def  = 1./8. !toutes les 3h
1767    !Config Help =
1768    !
1769    ecrit_hf_omp = 1./8.
[2702]1770    CALL getin('ecrit_hf',ecrit_hf_omp)
[1938]1771    !
1772    !Config Key  = ecrit_ins
1773    !Config Desc =
1774    !Config Def  = 1./48. ! toutes les 1/2 h
1775    !Config Help =
1776    !
1777    ecrit_ins_omp = 1./48.
[2702]1778    CALL getin('ecrit_ins',ecrit_ins_omp)
[1938]1779    !
1780    !Config Key  = ecrit_day
1781    !Config Desc =
1782    !Config Def  = 1.0 !tous les jours
1783    !Config Help = nombre de jours pour ecriture fichier histday.nc
1784    !
1785    ecrit_day_omp = 1.0
[2702]1786    CALL getin('ecrit_day',ecrit_day_omp)
[1938]1787    !
1788    !Config Key  = ecrit_mth
1789    !Config Desc =
1790    !Config Def  = 30. !tous les 30jours (1 fois par mois)
1791    !Config Help =
1792    !
1793    ecrit_mth_omp = 30.
[2702]1794    CALL getin('ecrit_mth',ecrit_mth_omp)
[1938]1795    !
1796    !Config Key  = ecrit_tra
1797    !Config Desc =
1798    !Config Def  = 30. !tous les 30jours (1 fois par mois)
1799    !Config Help =
1800    !
1801    ecrit_tra_omp = 0.
[2702]1802    CALL getin('ecrit_tra',ecrit_tra_omp)
[1938]1803    !
1804    !Config Key  = ecrit_reg
1805    !Config Desc =
1806    !Config Def  = 0.25  !4 fois par jour
1807    !Config Help =
1808    !
1809    ecrit_reg_omp = 0.25   !4 fois par jour
[2702]1810    CALL getin('ecrit_reg',ecrit_reg_omp)
[1938]1811    !
1812    !
[2240]1813    print*,'CONFPHYS OOK avant drag_ter'
[1938]1814    !
1815    ! PARAMETRES CDRAG
1816    !
1817    f_cdrag_ter_omp = 0.8
[2702]1818    CALL getin('f_cdrag_ter',f_cdrag_ter_omp)
[1938]1819    !
1820    f_cdrag_oce_omp = 0.8
[2702]1821    CALL getin('f_cdrag_oce',f_cdrag_oce_omp)
[1938]1822    !
[2240]1823
[2357]1824    ! Gustiness flags
[2254]1825    f_z0qh_oce_omp = 1.
[2702]1826    CALL getin('f_z0qh_oce',f_z0qh_oce_omp)
[2254]1827    !
[2240]1828    f_qsat_oce_omp = 1.
[2702]1829    CALL getin('f_qsat_oce',f_qsat_oce_omp)
[2240]1830    !
1831    f_gust_bl_omp = 0.
[2702]1832    CALL getin('f_gust_bl',f_gust_bl_omp)
[2240]1833    !
1834    f_gust_wk_omp = 0.
[2702]1835    CALL getin('f_gust_wk',f_gust_wk_omp)
[2240]1836    !
[2455]1837    !Config Key  = iflag_z0_oce
1838    !Config Desc = 0 (z0h=z0m), 1 (diff. equ. for z0h and z0m), -1 (z0m=z0h=z0min)
1839    !Config Def  = 0   ! z0h = z0m
1840    !Config Help =
1841    !
[2243]1842    iflag_z0_oce_omp=0
[2702]1843    CALL getin('iflag_z0_oce',iflag_z0_oce_omp)
[2243]1844    !
[2240]1845    iflag_gusts_omp=0
[2702]1846    CALL getin('iflag_gusts',iflag_gusts_omp)
[2240]1847    !
1848    min_wind_speed_omp = 1.
[2702]1849    CALL getin('min_wind_speed',min_wind_speed_omp)
[2240]1850
[2702]1851    z0m_seaice_omp = 0.002 ; CALL getin('z0m_seaice',z0m_seaice_omp)
1852    z0h_seaice_omp = 0.002 ; CALL getin('z0h_seaice',z0h_seaice_omp)
[2243]1853
[1938]1854    f_rugoro_omp = 0.
[2702]1855    CALL getin('f_rugoro',f_rugoro_omp)
[1687]1856
[2243]1857    z0min_omp = 0.000015
[2702]1858    CALL getin('z0min',z0min_omp)
[2243]1859
1860
[1938]1861    ! PARAMETERS FOR CONVECTIVE INHIBITION BY TROPOS. DRYNESS
1862    !
1863    !Config Key  = supcrit1
1864    !Config Desc =
1865    !Config Def  = .540
1866    !Config Help =
1867    !
1868    supcrit1_omp = .540
[2702]1869    CALL getin('supcrit1',supcrit1_omp)
[1687]1870
[1938]1871    !
1872    !Config Key  = supcrit2
1873    !Config Desc =
1874    !Config Def  = .600
1875    !Config Help =
1876    !
1877    supcrit2_omp = .600
[2702]1878    CALL getin('supcrit2',supcrit2_omp)
[1687]1879
[1938]1880    !
1881    ! PARAMETERS FOR THE MIXING DISTRIBUTION
1882    ! iflag_mix: 0=OLD,
1883    !            1=NEW (JYG),           
1884    !            2=NEW + conv. depth inhib. by tropos. dryness
1885    ! '2' is NOT operationnal and should not be used.
1886    !
1887    !Config Key  = iflag_mix
1888    !Config Desc =
1889    !Config Def  = 1
1890    !Config Help =
1891    !
1892    iflag_mix_omp = 1
[2702]1893    CALL getin('iflag_mix',iflag_mix_omp)
[1687]1894
[2420]1895!
1896    ! PARAMETERS FOR THE EROSION OF THE ADIABATIC ASCENTS
1897    ! iflag_mix_adiab: 0=OLD,
1898    !                  1=NEW (CR),           
1899    !           
[1938]1900    !
[2420]1901    !Config Key  = iflag_mix_adiab
1902    !Config Desc =
1903    !Config Def  = 1
1904    !Config Help =
1905    !
1906    iflag_mix_adiab_omp = 0
[2702]1907    CALL getin('iflag_mix_adiab',iflag_mix_adiab_omp)
[2420]1908
1909    !
[1938]1910    !Config Key  = scut
1911    !Config Desc =
1912    !Config Def  = 0.95
1913    !Config Help =
1914    !
1915    scut_omp = 0.95
[2702]1916    CALL getin('scut',scut_omp)
[1687]1917
[1938]1918    !
1919    !Config Key  = qqa1
1920    !Config Desc =
1921    !Config Def  = 1.0
1922    !Config Help =
1923    !
1924    qqa1_omp = 1.0
[2702]1925    CALL getin('qqa1',qqa1_omp)
[1687]1926
[1938]1927    !
1928    !Config Key  = qqa2
1929    !Config Desc =
1930    !Config Def  = 0.0
1931    !Config Help =
1932    !
1933    qqa2_omp = 0.0
[2702]1934    CALL getin('qqa2',qqa2_omp)
[1687]1935
[1938]1936    !
1937    !Config Key  = gammas
1938    !Config Desc =
1939    !Config Def  = 0.05
1940    !Config Help =
1941    !
1942    gammas_omp = 0.05
[2702]1943    CALL getin('gammas',gammas_omp)
[1687]1944
[1938]1945    !
1946    !Config Key  = Fmax
1947    !Config Desc =
1948    !Config Def  = 0.65
1949    !Config Help =
1950    !
1951    Fmax_omp = 0.65
[2702]1952    CALL getin('Fmax',Fmax_omp)
[1687]1953
[1938]1954    !
[2287]1955    !Config Key  = tmax_fonte_cv
1956    !Config Desc =
1957    !Config Def  = 275.15
1958    !Config Help =
1959    !
1960    tmax_fonte_cv_omp = 275.15
[2702]1961    CALL getin('tmax_fonte_cv',tmax_fonte_cv_omp)
[2287]1962
1963    !
[1938]1964    !Config Key  = alphas 
1965    !Config Desc =
1966    !Config Def  = -5.
1967    !Config Help =
1968    !
1969    alphas_omp = -5.
[2702]1970    CALL getin('alphas',alphas_omp)
[1687]1971
[1938]1972    !Config key = ok_strato
1973    !Config  Desc = activation de la version strato
1974    !Config  Def  = .FALSE.
[2110]1975    !Config  Help = active la version stratosph\'erique de LMDZ de F. Lott
[2357]1976    !               Et la sponge layer (Runs Stratospheriques)
[1687]1977
[1938]1978    ok_strato_omp=.FALSE.
1979    CALL getin('ok_strato',ok_strato_omp)
[1687]1980
[1938]1981    !Config  key = ok_hines
1982    !Config  Desc = activation de la parametrisation de hines
1983    !Config  Def  = .FALSE.
1984    !Config  Help = Clefs controlant la parametrization de Hines
[1687]1985
[1938]1986    ok_hines_omp=.FALSE.
1987    CALL getin('ok_hines',ok_hines_omp)
[1687]1988
[2357]1989    !  Parametres pour les ondes de gravite
1990    ! 
1991    !  Subgrid Scale Orography (Lott Miller (1997), Lott (1999))
1992
1993    sso_gkdrag_omp = merge(0.1875, 0.2, ok_strato_omp)
1994    CALL getin('sso_gkdrag', sso_gkdrag_omp)
1995
1996    sso_grahil_omp=merge(0.1,1.,ok_strato_omp)
1997    CALL getin('sso_grahil', sso_grahil_omp)
1998
1999    sso_grcrit_omp =merge(1.,0.01,ok_strato_omp)
2000    CALL getin('sso_grcrit', sso_grcrit_omp)
2001
2002    sso_gfrcri_omp = 1.
2003    CALL getin('sso_gfrcri', sso_gfrcri_omp)
2004
2005    sso_gkwake_omp = 0.50
2006    CALL getin('sso_gkwake', sso_gkwake_omp)
2007
2008    sso_gklift_omp = merge(0.25,0.50,ok_strato_omp)
2009    CALL getin('sso_gklift', sso_gklift_omp)
2010
[1938]2011    ! Random gravity waves:
[1687]2012
[1938]2013    ok_gwd_rando_omp = .FALSE.
[2179]2014    IF ( klon_glo == 1 ) THEN
2015       print*,'La parametrisation des ondes de gravites non orographiques'
2016       print*,'ne fonctionne pas en 1D'
2017    ELSE
2018       CALL getin('ok_gwd_rando', ok_gwd_rando_omp)
2019    ENDIF
[1687]2020
[2357]2021    gwd_rando_ruwmax_omp = 2.00
2022    CALL getin('gwd_rando_ruwmax', gwd_rando_ruwmax_omp)
[1687]2023
[2072]2024    gwd_rando_sat_omp = 0.25
2025    CALL getin('gwd_rando_sat', gwd_rando_sat_omp)
[1938]2026
[2357]2027    gwd_front_ruwmax_omp = 2.50
2028    CALL getin('gwd_front_ruwmax', gwd_front_ruwmax_omp)
2029
2030    gwd_front_sat_omp = 0.60
2031    CALL getin('gwd_front_sat', gwd_front_sat_omp)
2032
2033
[2136]2034    !Config  key = ok_qch4
2035    !Config  Desc = activation de la parametrisation du methane
2036    !Config  Def  = .FALSE.
2037    !Config  Help = Clef controlant l'activation de la parametrisation
2038    !               de l'humidite due a oxydation+photolyse du methane strato
2039
2040    ok_qch4_omp=.FALSE.
2041    CALL getin('ok_qch4',ok_qch4_omp)
2042
[1938]2043    !Config Key  = OK_LES                                               
2044    !Config Desc = Pour des sorties LES                                 
[2702]2045    !Config Def  = .FALSE.                                             
[1938]2046    !Config Help = Pour creer le fichier histLES contenant les sorties 
2047    !              LES                                                 
2048    !                                                                   
[2702]2049    ok_LES_omp = .FALSE.                                             
2050    CALL getin('OK_LES', ok_LES_omp)                                 
[1938]2051
2052    !Config Key  = callstats                                               
2053    !Config Desc = Pour des sorties callstats                                 
[2702]2054    !Config Def  = .FALSE.                                             
[1938]2055    !Config Help = Pour creer le fichier stats contenant les sorties 
2056    !              stats                                                 
2057    !                                                                   
[2702]2058    callstats_omp = .FALSE.                                             
2059    CALL getin('callstats', callstats_omp)                                 
[1938]2060    !
2061    !Config Key  = ecrit_LES
2062    !Config Desc = Frequence d'ecriture des resultats du LES en nombre de jours;
2063    !              par defaut 1., i.e. 1 jour
2064    !Config Def  = 1./8.
2065    !Config Help = ...
2066    !
2067    !
[2788]2068    adjust_tropopause = .FALSE.
2069    CALL getin('adjust_tropopause', adjust_tropopause_omp)
2070    !
2071    !Config Key  = adjust_tropopause
2072    !Config Desc = Adjust the ozone field from the climoz file by stretching its
2073    !              tropopause so that it matches the one of LMDZ.
2074    !Config Def  = .FALSE.
2075    !Config Help = Ensure tropospheric ozone column conservation.
2076    !
2077    !
[2820]2078    ok_daily_climoz = .FALSE.
[2788]2079    CALL getin('ok_daily_climoz', ok_daily_climoz_omp)
2080    !
2081    !Config Key  = ok_daily_climoz
2082    !Config Desc = Interpolate in time the ozone forcings within ce0l.
2083    !              .TRUE. if backward compatibility is needed.
2084    !Config Def  = .TRUE.
2085    !Config Help = .FALSE. ensure much fewer (no calendar dependency)
2086    !  and lighter monthly climoz files, inetrpolated in time at gcm run time.
2087    !
[1938]2088    ecrit_LES_omp = 1./8.
[2702]2089    CALL getin('ecrit_LES', ecrit_LES_omp)
[1938]2090    !
2091    read_climoz = 0 ! default value
[2702]2092    CALL getin('read_climoz', read_climoz)
[1938]2093
2094    carbon_cycle_tr_omp=.FALSE.
2095    CALL getin('carbon_cycle_tr',carbon_cycle_tr_omp)
2096
2097    carbon_cycle_cpl_omp=.FALSE.
2098    CALL getin('carbon_cycle_cpl',carbon_cycle_cpl_omp)
2099
2100    !$OMP END MASTER
2101    !$OMP BARRIER
2102
[1687]2103    R_ecc = R_ecc_omp
2104    R_peri = R_peri_omp
2105    R_incl = R_incl_omp
2106    solaire = solaire_omp
[2524]2107    ok_suntime_rrtm = ok_suntime_rrtm_omp
[1687]2108    co2_ppm = co2_ppm_omp
2109    RCO2 = RCO2_omp
2110    CH4_ppb = CH4_ppb_omp
2111    RCH4 = RCH4_omp
2112    N2O_ppb = N2O_ppb_omp
2113    RN2O = RN2O_omp
2114    CFC11_ppt = CFC11_ppt_omp
2115    RCFC11 = RCFC11_omp
2116    CFC12_ppt = CFC12_ppt_omp
2117    RCFC12 = RCFC12_omp
2118    RCO2_act = RCO2
2119    RCH4_act = RCH4
2120    RN2O_act = RN2O
2121    RCFC11_act = RCFC11
2122    RCFC12_act = RCFC12
[1737]2123    ok_4xCO2atm = ok_4xCO2atm_omp
[1687]2124    RCO2_per = RCO2_per_omp
2125    RCH4_per = RCH4_per_omp
2126    RN2O_per = RN2O_per_omp
2127    RCFC11_per = RCFC11_per_omp
2128    RCFC12_per = RCFC12_per_omp
[1938]2129
[1687]2130    cycle_diurne = cycle_diurne_omp
2131    soil_model = soil_model_omp
2132    new_oliq = new_oliq_omp
2133    ok_orodr = ok_orodr_omp
2134    ok_orolf = ok_orolf_omp
2135    ok_limitvrai = ok_limitvrai_omp
2136    nbapp_rad = nbapp_rad_omp
2137    iflag_con = iflag_con_omp
[2707]2138    nbapp_cv = nbapp_cv_omp
[2730]2139    nbapp_wk = nbapp_wk_omp
[1753]2140    iflag_ener_conserv = iflag_ener_conserv_omp
[2007]2141    ok_conserv_q = ok_conserv_q_omp
[1894]2142    iflag_fisrtilp_qsat = iflag_fisrtilp_qsat_omp
[2415]2143    iflag_bergeron = iflag_bergeron_omp
[1687]2144
2145    epmax = epmax_omp
[2481]2146    coef_epmax_cape = coef_epmax_cape_omp
[1687]2147    ok_adj_ema = ok_adj_ema_omp
2148    iflag_clw = iflag_clw_omp
2149    cld_lc_lsc = cld_lc_lsc_omp
2150    cld_lc_con = cld_lc_con_omp
2151    cld_tau_lsc = cld_tau_lsc_omp
2152    cld_tau_con = cld_tau_con_omp
2153    ffallv_lsc = ffallv_lsc_omp
2154    ffallv_con = ffallv_con_omp
2155    coef_eva = coef_eva_omp
2156    reevap_ice = reevap_ice_omp
2157    iflag_pdf = iflag_pdf_omp
2158    solarlong0 = solarlong0_omp
2159    qsol0 = qsol0_omp
[1894]2160    evap0 = evap0_omp
2161    albsno0 = albsno0_omp
[2915]2162    iflag_sic = iflag_sic_omp
[1687]2163    inertie_sol = inertie_sol_omp
[2915]2164    inertie_sic = inertie_sic_omp
2165    inertie_lic = inertie_lic_omp
[1687]2166    inertie_sno = inertie_sno_omp
2167    rad_froid = rad_froid_omp
2168    rad_chau1 = rad_chau1_omp
2169    rad_chau2 = rad_chau2_omp
2170    t_glace_min = t_glace_min_omp
2171    t_glace_max = t_glace_max_omp
[2006]2172    exposant_glace = exposant_glace_omp
2173    iflag_t_glace = iflag_t_glace_omp
[2547]2174    iflag_cloudth_vert=iflag_cloudth_vert_omp
[2945]2175    iflag_rain_incloud_vol=iflag_rain_incloud_vol_omp
[1849]2176    iflag_ice_thermo = iflag_ice_thermo_omp
[1687]2177    rei_min = rei_min_omp
2178    rei_max = rei_max_omp
2179    top_height = top_height_omp
2180    overlap = overlap_omp
2181    cdmmax = cdmmax_omp
2182    cdhmax = cdhmax_omp
2183    ksta = ksta_omp
2184    ksta_ter = ksta_ter_omp
[2126]2185    f_ri_cd_min = f_ri_cd_min_omp
[1687]2186    ok_kzmin = ok_kzmin_omp
[2561]2187    pbl_lmixmin_alpha=pbl_lmixmin_alpha_omp
[1687]2188    fmagic = fmagic_omp
2189    pmagic = pmagic_omp
2190    iflag_pbl = iflag_pbl_omp
[2159]2191    iflag_pbl_split = iflag_pbl_split_omp
[2455]2192    iflag_order2_sollw = iflag_order2_sollw_omp
[1687]2193    lev_histhf = lev_histhf_omp
2194    lev_histday = lev_histday_omp
2195    lev_histmth = lev_histmth_omp
2196    lev_histins = lev_histins_omp
2197    lev_histLES = lev_histLES_omp
2198    lev_histdayNMC = lev_histdayNMC_omp
[1828]2199    levout_histNMC = levout_histNMC_omp
[1687]2200    ok_histNMC(:) = ok_histNMC_omp(:)
2201    freq_outNMC(:) = freq_outNMC_omp(:)
2202    freq_calNMC(:) = freq_calNMC_omp(:)
2203
2204    type_ocean = type_ocean_omp
2205    version_ocean = version_ocean_omp
[2075]2206    t_coupl = t_coupl_omp
[1724]2207
[2702]2208    ok_veget=.TRUE.
[1724]2209    type_veget=type_veget_omp
[2702]2210    IF (type_veget=='n' .or. type_veget=='bucket' .or. type_veget=='betaclim') THEN
2211       ok_veget=.FALSE.
2212    ENDIF
[1865]2213    ! Martin
2214    ok_snow = ok_snow_omp
2215    ! Martin
[1724]2216
[2114]2217    ok_all_xml = ok_all_xml_omp
[1687]2218    ok_newmicro = ok_newmicro_omp
2219    ok_journe = ok_journe_omp
2220    ok_hf = ok_hf_omp
2221    ok_mensuel = ok_mensuel_omp
2222    ok_instan = ok_instan_omp
2223    freq_ISCCP = freq_ISCCP_omp
2224    ecrit_ISCCP = ecrit_ISCCP_omp
2225    freq_COSP = freq_COSP_omp
[2580]2226    freq_AIRS = freq_AIRS_omp
[1687]2227    ok_ade = ok_ade_omp
2228    ok_aie = ok_aie_omp
[2738]2229    ok_alw = ok_alw_omp
[1712]2230    ok_cdnc = ok_cdnc_omp
[1687]2231    aerosol_couple = aerosol_couple_omp
2232    flag_aerosol=flag_aerosol_omp
[1764]2233    flag_aerosol_strat=flag_aerosol_strat_omp
[2644]2234    flag_bc_internal_mixture=flag_bc_internal_mixture_omp
[1687]2235    new_aod=new_aod_omp
2236    aer_type = aer_type_omp
2237    bl95_b0 = bl95_b0_omp
2238    bl95_b1 = bl95_b1_omp
2239    fact_cldcon = fact_cldcon_omp
2240    facttemps = facttemps_omp
2241    ratqsbas = ratqsbas_omp
2242    ratqshaut = ratqshaut_omp
2243    tau_ratqs = tau_ratqs_omp
2244
2245    iflag_radia = iflag_radia_omp
2246    iflag_rrtm = iflag_rrtm_omp
[2305]2247    iflag_albedo = iflag_albedo_omp
2248    ok_chlorophyll = ok_chlorophyll_omp
[1989]2249    NSW = NSW_omp
[2236]2250    iflag_cld_th = iflag_cld_th_omp
[2205]2251    iflag_cld_cv = iflag_cld_cv_omp
2252    tau_cld_cv = tau_cld_cv_omp
2253    coefw_cld_cv = coefw_cld_cv_omp
[1687]2254    iflag_ratqs = iflag_ratqs_omp
2255    ip_ebil_phy = ip_ebil_phy_omp
2256    iflag_thermals = iflag_thermals_omp
2257    iflag_thermals_ed = iflag_thermals_ed_omp
[2000]2258    fact_thermals_ed_dz = fact_thermals_ed_dz_omp
[1687]2259    iflag_thermals_optflux = iflag_thermals_optflux_omp
[1998]2260    iflag_thermals_closure = iflag_thermals_closure_omp
[1687]2261    nsplit_thermals = nsplit_thermals_omp
2262    tau_thermals = tau_thermals_omp
2263    alp_bl_k = alp_bl_k_omp
[1938]2264    ! nrlmd le 10/04/2012
[1687]2265    iflag_trig_bl = iflag_trig_bl_omp
2266    s_trig = s_trig_omp
2267    tau_trig_shallow = tau_trig_shallow_omp
2268    tau_trig_deep = tau_trig_deep_omp
2269    iflag_clos_bl = iflag_clos_bl_omp
[1938]2270    ! fin nrlmd le 10/04/2012
[1687]2271    iflag_coupl = iflag_coupl_omp
2272    iflag_clos = iflag_clos_omp
2273    iflag_wake = iflag_wake_omp
[2201]2274    coef_clos_ls = coef_clos_ls_omp
[1687]2275    alp_offset = alp_offset_omp
2276    iflag_cvl_sigd = iflag_cvl_sigd_omp
2277    type_run = type_run_omp
2278    ok_cosp = ok_cosp_omp
[2580]2279    ok_airs = ok_airs_omp
2280
[1687]2281    ok_mensuelCOSP = ok_mensuelCOSP_omp
2282    ok_journeCOSP = ok_journeCOSP_omp
2283    ok_hfCOSP = ok_hfCOSP_omp
2284    seuil_inversion=seuil_inversion_omp
2285    lonmin_ins = lonmin_ins_omp
2286    lonmax_ins = lonmax_ins_omp
2287    latmin_ins = latmin_ins_omp
2288    latmax_ins = latmax_ins_omp
2289    ecrit_hf   = ecrit_hf_omp
2290    ecrit_ins   = ecrit_ins_omp
2291    ecrit_day = ecrit_day_omp
2292    ecrit_mth = ecrit_mth_omp
2293    ecrit_tra = ecrit_tra_omp
2294    ecrit_reg = ecrit_reg_omp
[2253]2295    cvl_comp_threshold = cvl_comp_threshold_omp
2296    cvl_sig2feed = cvl_sig2feed_omp
[1687]2297    cvl_corr = cvl_corr_omp
2298    ok_lic_melt = ok_lic_melt_omp
2299    f_cdrag_ter=f_cdrag_ter_omp
2300    f_cdrag_oce=f_cdrag_oce_omp
[2240]2301
2302    f_gust_wk=f_gust_wk_omp
2303    f_gust_bl=f_gust_bl_omp
2304    f_qsat_oce=f_qsat_oce_omp
[2254]2305    f_z0qh_oce=f_z0qh_oce_omp
[2240]2306    min_wind_speed=min_wind_speed_omp
2307    iflag_gusts=iflag_gusts_omp
[2243]2308    iflag_z0_oce=iflag_z0_oce_omp
[2240]2309
[2243]2310    z0m_seaice=z0m_seaice_omp
2311    z0h_seaice=z0h_seaice_omp
2312
[1687]2313    f_rugoro=f_rugoro_omp
[2243]2314
2315    z0min=z0min_omp
[1687]2316    supcrit1 = supcrit1_omp
2317    supcrit2 = supcrit2_omp
2318    iflag_mix = iflag_mix_omp
[2420]2319    iflag_mix_adiab = iflag_mix_adiab_omp
[1687]2320    scut = scut_omp
2321    qqa1 = qqa1_omp
2322    qqa2 = qqa2_omp
2323    gammas = gammas_omp
2324    Fmax = Fmax_omp
[2287]2325    tmax_fonte_cv = tmax_fonte_cv_omp
[1687]2326    alphas = alphas_omp
[2357]2327
2328    gkdrag=sso_gkdrag_omp
2329    grahilo=sso_grahil_omp
2330    grcrit=sso_grcrit_omp
2331    gfrcrit=sso_gfrcri_omp
2332    gkwake=sso_gkwake_omp
2333    gklift=sso_gklift_omp
2334
[1687]2335    ok_strato = ok_strato_omp
2336    ok_hines = ok_hines_omp
[1938]2337    ok_gwd_rando = ok_gwd_rando_omp
[2357]2338    gwd_rando_ruwmax = gwd_rando_ruwmax_omp
[2072]2339    gwd_rando_sat = gwd_rando_sat_omp
[2357]2340    gwd_front_ruwmax = gwd_front_ruwmax_omp
2341    gwd_front_sat = gwd_front_sat_omp
[2136]2342    ok_qch4 = ok_qch4_omp
[1687]2343    ok_LES = ok_LES_omp
2344    callstats = callstats_omp
2345    ecrit_LES = ecrit_LES_omp
[2788]2346    adjust_tropopause = adjust_tropopause_omp
2347    ok_daily_climoz = ok_daily_climoz_omp
[1687]2348    carbon_cycle_tr = carbon_cycle_tr_omp
2349    carbon_cycle_cpl = carbon_cycle_cpl_omp
2350
[1938]2351    ! Test of coherence between type_ocean and version_ocean
[1687]2352    IF (type_ocean=='couple' .AND. (version_ocean/='opa8' .AND. version_ocean/='nemo') ) THEN
2353       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid in coupled configuration'
[2311]2354       CALL abort_physic('conf_phys','version_ocean not valid',1)
[2702]2355    ENDIF
[1687]2356
2357    IF (type_ocean=='slab' .AND. version_ocean=='xxxxxx') THEN
2358       version_ocean='sicOBS'
[2057]2359    ELSE IF (type_ocean=='slab' .AND. version_ocean/='sicOBS' &
[2357]2360         .AND. version_ocean/='sicINT' .AND. version_ocean/='sicNO') THEN
[1687]2361       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean'
[2311]2362       CALL abort_physic('conf_phys','version_ocean not valid',1)
[2702]2363    ENDIF
[1687]2364
[2413]2365    !--test on radiative scheme
2366    IF (iflag_rrtm .EQ. 0) THEN
2367      IF (NSW.NE.2) THEN
2368        WRITE(lunout,*) ' ERROR iflag_rrtm=0 and NSW<>2 not possible'
2369        CALL abort_physic('conf_phys','choice NSW not valid',1)
2370      ENDIF
2371    ELSE IF (iflag_rrtm .EQ. 1) THEN
2372      IF (NSW.NE.2.AND.NSW.NE.4.AND.NSW.NE.6) THEN
2373        WRITE(lunout,*) ' ERROR iflag_rrtm=1 and NSW<>2,4,6 not possible'
2374        CALL abort_physic('conf_phys','choice NSW not valid',1)
2375      ENDIF
2376    ELSE
2377       WRITE(lunout,*) ' ERROR iflag_rrtm<>0,1'
2378       CALL abort_physic('conf_phys','choice iflag_rrtm not valid',1)
2379    ENDIF
[2701]2380#ifdef CPP_StratAer
2381    IF (iflag_rrtm .NE. 1) THEN
2382       WRITE(lunout,*) ' ERROR iflag_rrtm<>1 but StratAer activated'
2383       CALL abort_physic('conf_phys','iflag_rrtm not valid for StratAer',1)
2384    ENDIF
[2702]2385    IF (NSW .NE. 6) THEN
2386       WRITE(lunout,*) ' ERROR NSW<>6 but StratAer activated'
2387       CALL abort_physic('conf_phys','NSW not valid for StratAer',1)
2388    ENDIF
[2701]2389#endif
[2413]2390
2391    !--test on ocean surface albedo
2392    IF (iflag_albedo.LT.0.OR.iflag_albedo.GT.1) THEN
2393       WRITE(lunout,*) ' ERROR iflag_albedo<>0,1'
2394       CALL abort_physic('conf_phys','choice iflag_albedo not valid',1)
2395    ENDIF
2396
[1938]2397    ! Test sur new_aod. Ce flag permet de retrouver les resultats de l'AR4
2398    ! il n'est utilisable que lors du couplage avec le SO4 seul
[1687]2399    IF (ok_ade .OR. ok_aie) THEN
2400       IF ( flag_aerosol .EQ. 0 ) THEN
[2311]2401          CALL abort_physic('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
[2702]2402       ENDIF
[1687]2403       IF ( .NOT. new_aod .AND.  flag_aerosol .NE. 1) THEN
[2311]2404          CALL abort_physic('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
[2702]2405       ENDIF
2406    ENDIF
[1687]2407
[2456]2408    ! Flag_aerosol cannot be to zero if we are in coupled mode for aerosol
2409    IF (aerosol_couple .AND. flag_aerosol .eq. 0 ) THEN
2410       CALL abort_physic('conf_phys', 'flag_aerosol cannot be to zero if aerosol_couple=y ', 1)
2411    ENDIF
2412
2413    ! flag_aerosol need to be different to zero if ok_cdnc is activated
2414    IF (ok_cdnc .AND. flag_aerosol .eq. 0) THEN
2415       CALL abort_physic('conf_phys', 'flag_aerosol cannot be to zero if ok_cdnc is activated ', 1)
2416    ENDIF
2417
[1938]2418    ! ok_cdnc must be set to y if ok_aie is activated
[1712]2419    IF (ok_aie .AND. .NOT. ok_cdnc) THEN
[2311]2420       CALL abort_physic('conf_phys', 'ok_cdnc must be set to y if ok_aie is activated',1)
[1938]2421    ENDIF
[1712]2422
[2644]2423    ! BC internal mixture is only possible with RRTM & NSW=6 & flag_aerosol=6 or aerosol_couple
2424    IF (flag_bc_internal_mixture .AND. NSW.NE.6) THEN
2425       CALL abort_physic('conf_phys', 'flag_bc_internal_mixture can only be activated with NSW=6',1)
2426    ENDIF
2427    IF (flag_bc_internal_mixture .AND. iflag_rrtm.NE.1) THEN
2428       CALL abort_physic('conf_phys', 'flag_bc_internal_mixture can only be activated with RRTM',1)
2429    ENDIF
2430    IF (flag_bc_internal_mixture .AND. flag_aerosol.NE.6) THEN
2431       CALL abort_physic('conf_phys', 'flag_bc_internal_mixture can only be activated with flag_aerosol=6',1)
2432    ENDIF
2433
[1938]2434    !$OMP MASTER
[1687]2435
[1938]2436    write(lunout,*)' ##############################################'
2437    write(lunout,*)' Configuration des parametres de la physique: '
2438    write(lunout,*)' Type ocean = ', type_ocean
2439    write(lunout,*)' Version ocean = ', version_ocean
2440    write(lunout,*)' Config veget = ', ok_veget,type_veget
2441    write(lunout,*)' Snow model SISVAT : ok_snow = ', ok_snow
[2114]2442    write(lunout,*)' Config xml pour XIOS : ok_all_xml = ', ok_all_xml
[1938]2443    write(lunout,*)' Sortie journaliere = ', ok_journe
2444    write(lunout,*)' Sortie haute frequence = ', ok_hf
2445    write(lunout,*)' Sortie mensuelle = ', ok_mensuel
2446    write(lunout,*)' Sortie instantanee = ', ok_instan
2447    write(lunout,*)' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
2448    write(lunout,*)' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
2449    write(lunout,*)' Frequence appel simulateur COSP, freq_COSP =', freq_COSP
[2580]2450    write(lunout,*)' Frequence appel simulateur AIRS, freq_AIRS =', freq_AIRS
[1938]2451    write(lunout,*)' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
2452    write(lunout,*)' Excentricite = ',R_ecc
2453    write(lunout,*)' Equinoxe = ',R_peri
2454    write(lunout,*)' Inclinaison =',R_incl
2455    write(lunout,*)' Constante solaire =',solaire
[2524]2456    write(lunout,*)' ok_suntime_rrtm =',ok_suntime_rrtm
[1938]2457    write(lunout,*)' co2_ppm =',co2_ppm
2458    write(lunout,*)' RCO2_act = ',RCO2_act
2459    write(lunout,*)' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
2460    write(lunout,*)' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
2461    write(lunout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
2462    write(lunout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
2463    write(lunout,*)' ok_4xCO2atm=',ok_4xCO2atm
2464    write(lunout,*)' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
2465    write(lunout,*)' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
2466    write(lunout,*)' RCFC12_per = ',RCFC12_per
[2253]2467    write(lunout,*)' cvl_comp_threshold=', cvl_comp_threshold
2468    write(lunout,*)' cvl_sig2feed=', cvl_sig2feed
[1938]2469    write(lunout,*)' cvl_corr=', cvl_corr
2470    write(lunout,*)'ok_lic_melt=', ok_lic_melt
2471    write(lunout,*)'cycle_diurne=',cycle_diurne
2472    write(lunout,*)'soil_model=',soil_model
2473    write(lunout,*)'new_oliq=',new_oliq
2474    write(lunout,*)'ok_orodr=',ok_orodr
2475    write(lunout,*)'ok_orolf=',ok_orolf
2476    write(lunout,*)'ok_limitvrai=',ok_limitvrai
2477    write(lunout,*)'nbapp_rad=',nbapp_rad
2478    write(lunout,*)'iflag_con=',iflag_con
[2707]2479    write(lunout,*)'nbapp_cv=',nbapp_cv
[2730]2480    write(lunout,*)'nbapp_wk=',nbapp_wk
[1938]2481    write(lunout,*)'iflag_ener_conserv=',iflag_ener_conserv
[2007]2482    write(lunout,*)'ok_conserv_q=',ok_conserv_q
[1938]2483    write(lunout,*)'iflag_fisrtilp_qsat=',iflag_fisrtilp_qsat
[2415]2484    write(lunout,*)'iflag_bergeron=',iflag_bergeron
[1938]2485    write(lunout,*)' epmax = ', epmax
[2481]2486    write(lunout,*)' coef_epmax_cape = ', coef_epmax_cape
[1938]2487    write(lunout,*)' ok_adj_ema = ', ok_adj_ema
2488    write(lunout,*)' iflag_clw = ', iflag_clw
2489    write(lunout,*)' cld_lc_lsc = ', cld_lc_lsc
2490    write(lunout,*)' cld_lc_con = ', cld_lc_con
2491    write(lunout,*)' cld_tau_lsc = ', cld_tau_lsc
2492    write(lunout,*)' cld_tau_con = ', cld_tau_con
2493    write(lunout,*)' ffallv_lsc = ', ffallv_lsc
2494    write(lunout,*)' ffallv_con = ', ffallv_con
2495    write(lunout,*)' coef_eva = ', coef_eva
2496    write(lunout,*)' reevap_ice = ', reevap_ice
2497    write(lunout,*)' iflag_pdf = ', iflag_pdf
[2236]2498    write(lunout,*)' iflag_cld_th = ', iflag_cld_th
[2205]2499    write(lunout,*)' iflag_cld_cv = ', iflag_cld_cv
2500    write(lunout,*)' tau_cld_cv = ', tau_cld_cv
2501    write(lunout,*)' coefw_cld_cv = ', coefw_cld_cv
[1938]2502    write(lunout,*)' iflag_radia = ', iflag_radia
2503    write(lunout,*)' iflag_rrtm = ', iflag_rrtm
[1989]2504    write(lunout,*)' NSW = ', NSW
[2227]2505    write(lunout,*)' iflag_albedo = ', iflag_albedo !albedo SB
2506    write(lunout,*)' ok_chlorophyll =',ok_chlorophyll ! albedo SB
[1938]2507    write(lunout,*)' iflag_ratqs = ', iflag_ratqs
2508    write(lunout,*)' seuil_inversion = ', seuil_inversion
2509    write(lunout,*)' fact_cldcon = ', fact_cldcon
2510    write(lunout,*)' facttemps = ', facttemps
2511    write(lunout,*)' ok_newmicro = ',ok_newmicro
2512    write(lunout,*)' ratqsbas = ',ratqsbas
2513    write(lunout,*)' ratqshaut = ',ratqshaut
2514    write(lunout,*)' tau_ratqs = ',tau_ratqs
2515    write(lunout,*)' top_height = ',top_height
2516    write(lunout,*)' rad_froid = ',rad_froid
2517    write(lunout,*)' rad_chau1 = ',rad_chau1
2518    write(lunout,*)' rad_chau2 = ',rad_chau2
2519    write(lunout,*)' t_glace_min = ',t_glace_min
2520    write(lunout,*)' t_glace_max = ',t_glace_max
[2006]2521    write(lunout,*)' exposant_glace = ',exposant_glace
2522    write(lunout,*)' iflag_t_glace = ',iflag_t_glace
[2547]2523    write(lunout,*)' iflag_cloudth_vert = ',iflag_cloudth_vert
[2945]2524    write(lunout,*)' iflag_rain_incloud_vol = ',iflag_rain_incloud_vol
[1938]2525    write(lunout,*)' iflag_ice_thermo = ',iflag_ice_thermo
2526    write(lunout,*)' rei_min = ',rei_min
2527    write(lunout,*)' rei_max = ',rei_max
2528    write(lunout,*)' overlap = ',overlap
2529    write(lunout,*)' cdmmax = ',cdmmax
2530    write(lunout,*)' cdhmax = ',cdhmax
2531    write(lunout,*)' ksta = ',ksta
2532    write(lunout,*)' ksta_ter = ',ksta_ter
[2126]2533    write(lunout,*)' f_ri_cd_min = ',f_ri_cd_min
[1938]2534    write(lunout,*)' ok_kzmin = ',ok_kzmin
[2561]2535    write(lunout,*)' pbl_lmixmin_alpha = ',pbl_lmixmin_alpha
[1938]2536    write(lunout,*)' fmagic = ',fmagic
2537    write(lunout,*)' pmagic = ',pmagic
2538    write(lunout,*)' ok_ade = ',ok_ade
2539    write(lunout,*)' ok_aie = ',ok_aie
[2738]2540    write(lunout,*)' ok_alw = ',ok_alw
[1938]2541    write(lunout,*)' aerosol_couple = ', aerosol_couple
2542    write(lunout,*)' flag_aerosol = ', flag_aerosol
[2788]2543    write(lunout,*)' flag_aerosol_strat= ', flag_aerosol_strat
[1938]2544    write(lunout,*)' new_aod = ', new_aod
2545    write(lunout,*)' aer_type = ',aer_type
2546    write(lunout,*)' bl95_b0 = ',bl95_b0
2547    write(lunout,*)' bl95_b1 = ',bl95_b1
2548    write(lunout,*)' lev_histhf = ',lev_histhf
2549    write(lunout,*)' lev_histday = ',lev_histday
2550    write(lunout,*)' lev_histmth = ',lev_histmth
2551    write(lunout,*)' lev_histins = ',lev_histins
2552    write(lunout,*)' lev_histLES = ',lev_histLES
2553    write(lunout,*)' lev_histdayNMC = ',lev_histdayNMC
2554    write(lunout,*)' levout_histNMC = ',levout_histNMC
2555    write(lunout,*)' ok_histNMC = ',ok_histNMC
2556    write(lunout,*)' freq_outNMC = ',freq_outNMC
2557    write(lunout,*)' freq_calNMC = ',freq_calNMC
2558    write(lunout,*)' iflag_pbl = ', iflag_pbl
[2159]2559    write(lunout,*)' iflag_pbl_split = ', iflag_pbl_split
[2455]2560    write(lunout,*)' iflag_order2_sollw = ', iflag_order2_sollw
[1938]2561    write(lunout,*)' iflag_thermals = ', iflag_thermals
2562    write(lunout,*)' iflag_thermals_ed = ', iflag_thermals_ed
[2000]2563    write(lunout,*)' fact_thermals_ed_dz = ', fact_thermals_ed_dz
[1938]2564    write(lunout,*)' iflag_thermals_optflux = ', iflag_thermals_optflux
[1998]2565    write(lunout,*)' iflag_thermals_closure = ', iflag_thermals_closure
[1938]2566    write(lunout,*)' iflag_clos = ', iflag_clos
[2201]2567    write(lunout,*)' coef_clos_ls = ', coef_clos_ls
[1938]2568    write(lunout,*)' type_run = ',type_run
2569    write(lunout,*)' ok_cosp = ',ok_cosp
[2580]2570    write(lunout,*)' ok_airs = ',ok_airs
2571
[1938]2572    write(lunout,*)' ok_mensuelCOSP = ',ok_mensuelCOSP
2573    write(lunout,*)' ok_journeCOSP = ',ok_journeCOSP
2574    write(lunout,*)' ok_hfCOSP =',ok_hfCOSP
2575    write(lunout,*)' solarlong0 = ', solarlong0
2576    write(lunout,*)' qsol0 = ', qsol0
2577    write(lunout,*)' evap0 = ', evap0
2578    write(lunout,*)' albsno0 = ', albsno0
[2915]2579    write(lunout,*)' iflag_sic = ', iflag_sic
[1938]2580    write(lunout,*)' inertie_sol = ', inertie_sol
[2915]2581    write(lunout,*)' inertie_sic = ', inertie_sic
2582    write(lunout,*)' inertie_lic = ', inertie_lic
[1938]2583    write(lunout,*)' inertie_sno = ', inertie_sno
2584    write(lunout,*)' f_cdrag_ter = ',f_cdrag_ter
2585    write(lunout,*)' f_cdrag_oce = ',f_cdrag_oce
2586    write(lunout,*)' f_rugoro = ',f_rugoro
[2243]2587    write(lunout,*)' z0min = ',z0min
[1938]2588    write(lunout,*)' supcrit1 = ', supcrit1
2589    write(lunout,*)' supcrit2 = ', supcrit2
2590    write(lunout,*)' iflag_mix = ', iflag_mix
[2420]2591    write(lunout,*)' iflag_mix_adiab = ', iflag_mix_adiab
[1938]2592    write(lunout,*)' scut = ', scut
2593    write(lunout,*)' qqa1 = ', qqa1
2594    write(lunout,*)' qqa2 = ', qqa2
2595    write(lunout,*)' gammas = ', gammas
2596    write(lunout,*)' Fmax = ', Fmax
[2287]2597    write(lunout,*)' tmax_fonte_cv = ', tmax_fonte_cv
[1938]2598    write(lunout,*)' alphas = ', alphas
2599    write(lunout,*)' iflag_wake = ', iflag_wake
2600    write(lunout,*)' alp_offset = ', alp_offset
2601    ! nrlmd le 10/04/2012
2602    write(lunout,*)' iflag_trig_bl = ', iflag_trig_bl
2603    write(lunout,*)' s_trig = ', s_trig
2604    write(lunout,*)' tau_trig_shallow = ', tau_trig_shallow
2605    write(lunout,*)' tau_trig_deep = ', tau_trig_deep
2606    write(lunout,*)' iflag_clos_bl = ', iflag_clos_bl
2607    ! fin nrlmd le 10/04/2012
[1687]2608
[1938]2609    write(lunout,*)' lonmin lonmax latmin latmax bilKP_ins =',&
2610         lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
2611    write(lunout,*)' ecrit_ hf, ins, day, mth, reg, tra, ISCCP, LES',&
2612         ecrit_hf, ecrit_ins, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra, ecrit_ISCCP, ecrit_LES
[1687]2613
[1938]2614    write(lunout,*) 'ok_strato = ', ok_strato
2615    write(lunout,*) 'ok_hines = ',  ok_hines
2616    write(lunout,*) 'ok_gwd_rando = ',  ok_gwd_rando
[2136]2617    write(lunout,*) 'ok_qch4 = ',  ok_qch4
[2357]2618    write(lunout,*) 'gwd_rando_ruwmax = ', gwd_rando_ruwmax
[2072]2619    write(lunout,*) 'gwd_rando_sat = ', gwd_rando_sat
[2357]2620    write(lunout,*) 'gwd_front_ruwmax = ', gwd_front_ruwmax
2621    write(lunout,*) 'gwd_front_sat = ', gwd_front_sat
2622    write(lunout,*) 'SSO gkdrag =',gkdrag
2623    write(lunout,*) 'SSO grahilo=',grahilo
2624    write(lunout,*) 'SSO grcrit=',grcrit
2625    write(lunout,*) 'SSO gfrcrit=',gfrcrit
2626    write(lunout,*) 'SSO gkwake=',gkwake
2627    write(lunout,*) 'SSO gklift=',gklift
[2788]2628    write(lunout,*) 'adjust_tropopause = ', adjust_tropopause
2629    write(lunout,*) 'ok_daily_climoz = ',ok_daily_climoz
[1938]2630    write(lunout,*) 'read_climoz = ', read_climoz
2631    write(lunout,*) 'carbon_cycle_tr = ', carbon_cycle_tr
2632    write(lunout,*) 'carbon_cycle_cpl = ', carbon_cycle_cpl
[1687]2633
[1938]2634    !$OMP END MASTER
2635
[2702]2636    RETURN
[1938]2637
[2702]2638  END SUBROUTINE conf_phys
[1687]2639
[2702]2640END MODULE conf_phys_m
[1687]2641!
2642!#################################################################
2643!
2644
[2702]2645SUBROUTINE conf_interface(tau_calv)
[1687]2646
[2702]2647  USE IOIPSL
[2311]2648  USE print_control_mod, ONLY: lunout
[2702]2649  IMPLICIT NONE
[1938]2650  ! Configuration de l'interace atm/surf
2651  !
2652  ! tau_calv:    temps de relaxation pour la fonte des glaciers
[1687]2653
2654  REAL          :: tau_calv
2655  REAL,SAVE     :: tau_calv_omp
2656
[1938]2657  !
2658  !Config Key  = tau_calv
2659  !Config Desc = temps de relaxation pour fonte des glaciers en jours
2660  !Config Def  = 1 an
2661  !Config Help =
2662  !
[1687]2663  tau_calv_omp = 360.*10.
[1938]2664  !$OMP MASTER
[2702]2665  CALL getin('tau_calv',tau_calv_omp)
[1938]2666  !$OMP END MASTER
2667  !$OMP BARRIER
[1687]2668
2669  tau_calv=tau_calv_omp
[1938]2670
2671  !$OMP MASTER
[1687]2672  write(lunout,*)' ##############################################'
2673  WRITE(lunout,*)' Configuration de l''interface atm/surfaces  : '
2674  WRITE(lunout,*)' tau_calv = ',tau_calv
[1938]2675  !$OMP END MASTER
[1687]2676
[2702]2677  RETURN
[1687]2678
[2702]2679END SUBROUTINE conf_interface
Note: See TracBrowser for help on using the repository browser.