source: LMDZ6/trunk/libf/phylmd/conf_phys_m.f90 @ 5474

Last change on this file since 5474 was 5470, checked in by evignon, 3 days ago

raffinement de la condition pour ne pas activer la param d'orographie sous maille
sur les terrains pentus non montagneux tels que les calottes. On raisonne désormais sur un proxy
du nombre de montagnes sous-maille. Travail de Valentin et Etienne

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