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

Last change on this file since 4678 was 4645, checked in by acozic, 10 months ago

modify name of parameter to read in case we want to coupled dms between ocean and atmosphere
Like this we will read the same parameter for the same coupling

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