GCC Code Coverage Report


Directory: ./
File: phys/conf_phys_m.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 1046 1089 96.1%
Branches: 37 126 29.4%

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