source: LMDZ5/trunk/libf/phylmd/conf_phys_m.F90 @ 2740

Last change on this file since 2740 was 2738, checked in by oboucher, 7 years ago

Swapping the order of CSSO4 and ASSO4 aerosols (and fixing an issue on aerindex). Preparing the ground for nitrate aerosols (coarse soluble, accumulation soluble, coarse insoluble). Modifying the LW aeropt routine so that it is compatible with both INCA and climatological aerosols (for dust only). Adding a new flag ok_alw for activating aerosol direct LW effect (for dust only). This change is bit comparable for flag_aerosol=6, flag_rrtm=1, NSW=6.

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