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

Last change on this file since 4390 was 4380, checked in by evignon, 21 months ago

premier commit d'un travail en cours sur l'externalisation de la routine lscp pour l'utilisation du replay
+ nettoyage

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