source: CONFIG/UNIFORM/v6/IPSLCM6.3/SOURCES/LMDZ/conf_phys_m.F90 @ 6571

Last change on this file since 6571 was 6571, checked in by acosce, 10 months ago

Add sources to update code for coupling between inca and pisces (remove cpp key)

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