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

Last change on this file since 4038 was 3999, checked in by evignon, 3 years ago

commission de la nouvelle routine de condensation
grande echelle simplifiee (lscp, version epuree de fistilp)
et du schema de nuages de phase mixte (en developpement)

La routine lscp n'est active que sous flag
ok_new_lscp=y

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