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

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

Put under the ok_lic_cond flag the option of depositing water vapour
onto snow, especially over ice sheets (lic). The default for the flag is
FALSE in order to keep backward compatibility, but should be turned to TRUE
in order to close the water budget. Tested in CM6.0.11.

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