source: LMDZ6/trunk/libf/phylmd/conf_phys_m.F90 @ 4462

Last change on this file since 4462 was 4458, checked in by evignon, 19 months ago

mise des seuils d'activation des params de SSO sous flag
pour faciliter les tests de sensibilité à venir

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