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

Last change on this file since 4744 was 4722, checked in by Laurent Fairhead, 9 months ago

Modification by O. Torres to the cdrag routines to include different bulk formulae
to calculate cdrag coefficients over ocean as well as an iteration of that
calculation.
The iteration is controlled by flag ok_cdrag_iter which if set to FALSE by default
to converge with previous results.
The choice of bulk formulae is set with the choix_bulk parameter
The number of iterations to run is set with nit_bulk
OT, PB, CD, LF

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