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

Last change on this file since 3630 was 3630, checked in by Laurent Fairhead, 4 years ago

Parameter new_aod is not needed anymore as it is assumed to be true
all the time. This means that we cannot replay AR4 simulations with new
LMDZ sources (we probably couldn't anyway)
LF, OB

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