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