Ignore:
Timestamp:
Nov 14, 2016, 6:15:27 PM (8 years ago)
Author:
oboucher
Message:

Adding one more test for StratAer? on NSW
Cleaning up the routine

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/conf_phys_m.F90

    r2701 r2702  
    44!
    55!
    6 module conf_phys_m
    7 
    8   implicit none
    9 
    10 contains
    11 
    12   subroutine conf_phys(ok_journe, ok_mensuel, ok_instan, ok_hf, &
     6MODULE conf_phys_m
     7
     8  IMPLICIT NONE
     9
     10CONTAINS
     11
     12  SUBROUTINE conf_phys(ok_journe, ok_mensuel, ok_instan, ok_hf, &
    1313       ok_LES,&
    1414       callstats,&
     
    2323       alp_offset)
    2424
    25     use IOIPSL
     25    USE IOIPSL
    2626    USE surface_data
    2727    USE phys_cal_mod
    28     USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl
    29     USE mod_grid_phy_lmdz, only: klon_glo
     28    USE carbon_cycle_mod,  ONLY: carbon_cycle_tr, carbon_cycle_cpl
     29    USE mod_grid_phy_lmdz, ONLY: klon_glo
    3030    USE print_control_mod, ONLY: lunout
    31 
    3231
    3332    include "conema3.h"
     
    7069
    7170    ! Sortie:
    72     logical              :: ok_newmicro
    73     integer              :: iflag_radia
    74     logical              :: ok_journe, ok_mensuel, ok_instan, ok_hf
    75     logical              :: ok_LES
     71    LOGICAL              :: ok_newmicro
     72    INTEGER              :: iflag_radia
     73    LOGICAL              :: ok_journe, ok_mensuel, ok_instan, ok_hf
     74    LOGICAL              :: ok_LES
    7675    LOGICAL              :: callstats
    7776    LOGICAL              :: ok_ade, ok_aie, ok_cdnc, aerosol_couple
     
    8180    LOGICAL              :: new_aod
    8281    REAL                 :: bl95_b0, bl95_b1
    83     real                 :: fact_cldcon, facttemps,ratqsbas,ratqshaut,tau_ratqs
    84     integer              :: iflag_cld_th
    85     integer              :: iflag_ratqs
    86 
    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
    96     LOGICAL,SAVE        :: ok_ade_omp, ok_aie_omp, ok_cdnc_omp, aerosol_couple_omp
     82    REAL                 :: fact_cldcon, facttemps,ratqsbas,ratqshaut,tau_ratqs
     83    INTEGER              :: iflag_cld_th
     84    INTEGER              :: iflag_ratqs
     85
     86    CHARACTER (len = 6), SAVE  :: type_ocean_omp, version_ocean_omp, ocean_omp
     87    CHARACTER (len = 10),SAVE  :: type_veget_omp
     88    CHARACTER (len = 8), SAVE  :: aer_type_omp
     89    LOGICAL, SAVE       :: ok_snow_omp
     90    LOGICAL, SAVE       :: ok_newmicro_omp
     91    LOGICAL, SAVE       :: ok_all_xml_omp
     92    LOGICAL, SAVE       :: ok_journe_omp, ok_mensuel_omp, ok_instan_omp, ok_hf_omp       
     93    LOGICAL, SAVE       :: ok_LES_omp   
     94    LOGICAL, SAVE       :: callstats_omp
     95    LOGICAL, SAVE       :: ok_ade_omp, ok_aie_omp, ok_cdnc_omp, aerosol_couple_omp
    9796    INTEGER, SAVE       :: flag_aerosol_omp
    9897    INTEGER, SAVE       :: flag_aerosol_strat_omp
     
    102101    REAL,SAVE           :: freq_ISCCP_omp, ecrit_ISCCP_omp
    103102    REAL,SAVE           :: freq_COSP_omp, freq_AIRS_omp
    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
    107 
    108 
    109     real,SAVE           :: ratqshaut_omp
    110     real,SAVE           :: tau_ratqs_omp
     103    REAL,SAVE           :: fact_cldcon_omp, facttemps_omp,ratqsbas_omp
     104    REAL,SAVE           :: tau_cld_cv_omp, coefw_cld_cv_omp
     105    INTEGER, SAVE       :: iflag_cld_cv_omp
     106
     107
     108    REAL, SAVE          :: ratqshaut_omp
     109    REAL, SAVE          :: tau_ratqs_omp
    111110    REAL, SAVE          :: t_coupl_omp
    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
    119 
    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
    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
     111    INTEGER, SAVE       :: iflag_radia_omp
     112    INTEGER, SAVE       :: iflag_rrtm_omp
     113    INTEGER, SAVE       :: iflag_albedo_omp !albedo SB
     114    LOGICAL, SAVE       :: ok_chlorophyll_omp ! albedo SB 
     115    INTEGER, SAVE       :: NSW_omp
     116    INTEGER, SAVE       :: iflag_cld_th_omp, ip_ebil_phy_omp
     117    INTEGER, SAVE       :: iflag_ratqs_omp
     118
     119    Real, SAVE          :: f_cdrag_ter_omp,f_cdrag_oce_omp
     120    Real, SAVE          :: f_rugoro_omp   , z0min_omp
     121    Real, SAVE          :: z0m_seaice_omp,z0h_seaice_omp
     122    REAL, SAVE          :: min_wind_speed_omp,f_gust_wk_omp,f_gust_bl_omp,f_qsat_oce_omp, f_z0qh_oce_omp
     123    INTEGER, SAVE       :: iflag_gusts_omp,iflag_z0_oce_omp
    125124
    126125    ! Local
    127     real                 :: zzz
    128 
    129     real :: seuil_inversion
    130     real,save :: seuil_inversion_omp
    131 
    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
     126    REAL                 :: zzz
     127
     128    REAL :: seuil_inversion
     129    REAL,SAVE :: seuil_inversion_omp
     130
     131    INTEGER,SAVE :: iflag_thermals_ed_omp,iflag_thermals_optflux_omp,iflag_thermals_closure_omp
     132    REAL, SAVE :: fact_thermals_ed_dz_omp
     133    INTEGER,SAVE :: iflag_thermals_omp,nsplit_thermals_omp
     134    REAL,SAVE :: tau_thermals_omp,alp_bl_k_omp
    136135    ! nrlmd le 10/04/2012
    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
     136    INTEGER,SAVE :: iflag_trig_bl_omp,iflag_clos_bl_omp
     137    INTEGER,SAVE :: tau_trig_shallow_omp,tau_trig_deep_omp
     138    REAL,SAVE    :: s_trig_omp
    140139    ! fin nrlmd le 10/04/2012
    141     real :: alp_offset
     140    REAL :: alp_offset
    142141    REAL, SAVE :: alp_offset_omp
    143     integer,SAVE :: iflag_coupl_omp,iflag_clos_omp,iflag_wake_omp
    144     integer,SAVE :: iflag_cvl_sigd_omp
     142    INTEGER,SAVE :: iflag_coupl_omp,iflag_clos_omp,iflag_wake_omp
     143    INTEGER,SAVE :: iflag_cvl_sigd_omp
    145144    REAL, SAVE :: coef_clos_ls_omp
    146145    REAL, SAVE :: supcrit1_omp, supcrit2_omp
    147146    INTEGER, SAVE :: iflag_mix_omp
    148147    INTEGER, SAVE :: iflag_mix_adiab_omp
    149     real, save :: scut_omp, qqa1_omp, qqa2_omp, gammas_omp, Fmax_omp, alphas_omp
     148    REAL, SAVE :: scut_omp, qqa1_omp, qqa2_omp, gammas_omp, Fmax_omp, alphas_omp
    150149    REAL, SAVE :: tmax_fonte_cv_omp
    151150
     
    187186    INTEGER,SAVE :: iflag_pbl_split_omp
    188187    INTEGER,SAVE :: iflag_order2_sollw_omp
    189     Integer, save :: lev_histins_omp, lev_histLES_omp
     188    Integer, SAVE :: lev_histins_omp, lev_histLES_omp
    190189    INTEGER, SAVE :: lev_histdayNMC_omp
    191190    INTEGER, SAVE :: levout_histNMC_omp(3)
     
    205204    LOGICAL,SAVE :: ok_lic_melt_omp
    206205    !
    207     LOGICAL,SAVE :: cycle_diurne_omp,soil_model_omp,new_oliq_omp
    208     LOGICAL,SAVE :: ok_orodr_omp, ok_orolf_omp, ok_limitvrai_omp
     206    LOGICAL,SAVE  :: cycle_diurne_omp,soil_model_omp,new_oliq_omp
     207    LOGICAL,SAVE  :: ok_orodr_omp, ok_orolf_omp, ok_limitvrai_omp
    209208    INTEGER, SAVE :: nbapp_rad_omp, iflag_con_omp
    210209    INTEGER, SAVE :: iflag_ener_conserv_omp
     
    212211    INTEGER, SAVE :: iflag_fisrtilp_qsat_omp
    213212    INTEGER, SAVE :: iflag_bergeron_omp
    214     LOGICAL,SAVE :: ok_strato_omp
    215     LOGICAL,SAVE :: ok_hines_omp, ok_gwd_rando_omp
    216     real, SAVE:: gwd_rando_ruwmax_omp, gwd_rando_sat_omp
    217     real, SAVE:: gwd_front_ruwmax_omp, gwd_front_sat_omp
    218     real, save:: sso_gkdrag_omp,sso_grahil_omp,sso_grcrit_omp
    219     real, save:: sso_gfrcri_omp,sso_gkwake_omp,sso_gklift_omp
    220     LOGICAL,SAVE :: ok_qch4_omp
    221     LOGICAL,SAVE      :: carbon_cycle_tr_omp
    222     LOGICAL,SAVE      :: carbon_cycle_cpl_omp
    223 
    224     integer, intent(out):: read_climoz ! read ozone climatology, OpenMP shared
     213    LOGICAL,SAVE  :: ok_strato_omp
     214    LOGICAL,SAVE  :: ok_hines_omp, ok_gwd_rando_omp
     215    REAL, SAVE    :: gwd_rando_ruwmax_omp, gwd_rando_sat_omp
     216    REAL, SAVE    :: gwd_front_ruwmax_omp, gwd_front_sat_omp
     217    REAL, SAVE    :: sso_gkdrag_omp,sso_grahil_omp,sso_grcrit_omp
     218    REAL, SAVE    :: sso_gfrcri_omp,sso_gkwake_omp,sso_gklift_omp
     219    LOGICAL,SAVE  :: ok_qch4_omp
     220    LOGICAL,SAVE  :: carbon_cycle_tr_omp
     221    LOGICAL,SAVE  :: carbon_cycle_cpl_omp
     222
     223    INTEGER, INTENT(OUT):: read_climoz ! read ozone climatology, OpenMP shared
    225224    ! Allowed values are 0, 1 and 2
    226225    ! 0: do not read an ozone climatology
     
    239238    !
    240239    type_ocean_omp = 'force '
    241     call getin('type_ocean', type_ocean_omp)
     240    CALL getin('type_ocean', type_ocean_omp)
    242241    !
    243242    !Config Key  = version_ocean
     
    247246    !
    248247    version_ocean_omp = 'xxxxxx'
    249     call getin('version_ocean', version_ocean_omp)
     248    CALL getin('version_ocean', version_ocean_omp)
    250249
    251250    !Config Key  = OCEAN
     
    255254    !
    256255    ocean_omp = 'yyyyyy'
    257     call getin('OCEAN', ocean_omp)
     256    CALL getin('OCEAN', ocean_omp)
    258257    IF (ocean_omp /= 'yyyyyy') THEN
    259258       WRITE(lunout,*)'ERROR! Old variable name OCEAN used in parmeter file.'
     
    261260       WRITE(lunout,*)'You have to update your parameter file physiq.def to succed running'
    262261       CALL abort_physic('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
    263     END IF
     262    ENDIF
    264263
    265264    !Config Key  = t_coupl
     
    269268    !
    270269    t_coupl_omp = 86400.
    271     call getin('t_coupl', t_coupl_omp)
     270    CALL getin('t_coupl', t_coupl_omp)
    272271    IF (t_coupl_omp == 0) THEN
    273272       WRITE(lunout,*)'ERROR! Timestep of coupling between atmosphere and ocean'
    274273       WRITE(lunout,*)'cannot be zero.'
    275274       CALL abort_physic('conf_phys','t_coupl = 0.',1)
    276     END IF
     275    ENDIF
    277276
    278277    !
    279278    !Config Key  = ok_all_xml
    280279    !Config Desc = utiliser les xml pourles définitions des champs pour xios
    281     !Config Def  = .false.
    282     !Config Help =
    283     !
    284     ok_all_xml_omp = .false.
    285     call getin('ok_all_xml', ok_all_xml_omp)
     280    !Config Def  = .FALSE.
     281    !Config Help =
     282    !
     283    ok_all_xml_omp = .FALSE.
     284    CALL getin('ok_all_xml', ok_all_xml_omp)
    286285    !
    287286
     
    289288    !Config Key  = VEGET
    290289    !Config Desc = Type de modele de vegetation
    291     !Config Def  = .false.
     290    !Config Def  = .FALSE.
    292291    !Config Help = Type de modele de vegetation utilise
    293292    !
    294293    type_veget_omp ='orchidee'
    295     call getin('VEGET', type_veget_omp)
     294    CALL getin('VEGET', type_veget_omp)
    296295    !
    297296
     
    299298    !Config Key  = ok_snow
    300299    !Config Desc = Flag to activate snow model SISVAT
    301     !Config Def  = .false.
    302     ok_snow_omp = .false.
    303     call getin('ok_snow', ok_snow_omp)
     300    !Config Def  = .FALSE.
     301    ok_snow_omp = .FALSE.
     302    CALL getin('ok_snow', ok_snow_omp)
    304303    ! Martin
    305304
    306305    !Config Key  = OK_journe
    307306    !Config Desc = Pour des sorties journalieres
    308     !Config Def  = .false.
     307    !Config Def  = .FALSE.
    309308    !Config Help = Pour creer le fichier histday contenant les sorties
    310309    !              journalieres
    311310    !
    312     ok_journe_omp = .false.
    313     call getin('OK_journe', ok_journe_omp)
     311    ok_journe_omp = .FALSE.
     312    CALL getin('OK_journe', ok_journe_omp)
    314313    !
    315314    !Config Key  = ok_hf
    316315    !Config Desc = Pour des sorties haute frequence
    317     !Config Def  = .false.
     316    !Config Def  = .FALSE.
    318317    !Config Help = Pour creer le fichier histhf contenant les sorties
    319318    !              haute frequence ( 3h ou 6h)
    320319    !
    321     ok_hf_omp = .false.
    322     call getin('ok_hf', ok_hf_omp)
     320    ok_hf_omp = .FALSE.
     321    CALL getin('ok_hf', ok_hf_omp)
    323322    !
    324323    !Config Key  = OK_mensuel
    325324    !Config Desc = Pour des sorties mensuelles
    326     !Config Def  = .true.
     325    !Config Def  = .TRUE.
    327326    !Config Help = Pour creer le fichier histmth contenant les sorties
    328327    !              mensuelles
    329328    !
    330     ok_mensuel_omp = .true.
    331     call getin('OK_mensuel', ok_mensuel_omp)
     329    ok_mensuel_omp = .TRUE.
     330    CALL getin('OK_mensuel', ok_mensuel_omp)
    332331    !
    333332    !Config Key  = OK_instan
    334333    !Config Desc = Pour des sorties instantanees
    335     !Config Def  = .false.
     334    !Config Def  = .FALSE.
    336335    !Config Help = Pour creer le fichier histins contenant les sorties
    337336    !              instantanees
    338337    !
    339     ok_instan_omp = .false.
    340     call getin('OK_instan', ok_instan_omp)
     338    ok_instan_omp = .FALSE.
     339    CALL getin('OK_instan', ok_instan_omp)
    341340    !
    342341    !Config Key  = ok_ade
    343342    !Config Desc = Aerosol direct effect or not?
    344     !Config Def  = .false.
     343    !Config Def  = .FALSE.
    345344    !Config Help = Used in radlwsw.F
    346345    !
    347     ok_ade_omp = .false.
    348     call getin('ok_ade', ok_ade_omp)
     346    ok_ade_omp = .FALSE.
     347    CALL getin('ok_ade', ok_ade_omp)
    349348
    350349    !
    351350    !Config Key  = ok_aie
    352351    !Config Desc = Aerosol indirect effect or not?
    353     !Config Def  = .false.
     352    !Config Def  = .FALSE.
    354353    !Config Help = Used in nuage.F and radlwsw.F
    355354    !
    356     ok_aie_omp = .false.
    357     call getin('ok_aie', ok_aie_omp)
     355    ok_aie_omp = .FALSE.
     356    CALL getin('ok_aie', ok_aie_omp)
    358357
    359358    !
    360359    !Config Key  = ok_cdnc
    361360    !Config Desc = ok cloud droplet number concentration
    362     !Config Def  = .false.
     361    !Config Def  = .FALSE.
    363362    !Config Help = Used in newmicro.F
    364363    !
    365     ok_cdnc_omp = .false.
    366     call getin('ok_cdnc', ok_cdnc_omp)
     364    ok_cdnc_omp = .FALSE.
     365    CALL getin('ok_cdnc', ok_cdnc_omp)
    367366    !
    368367    !Config Key  = aerosol_couple
    369368    !Config Desc = read aerosol in file or calcul by inca
    370     !Config Def  = .false.
     369    !Config Def  = .FALSE.
    371370    !Config Help = Used in physiq.F
    372371    !
    373     aerosol_couple_omp = .false.
     372    aerosol_couple_omp = .FALSE.
    374373    CALL getin('aerosol_couple',aerosol_couple_omp)
    375374    !
     
    410409    !Config Help = Used in physiq.F / aeropt
    411410    !
    412     flag_bc_internal_mixture_omp = .false.
     411    flag_bc_internal_mixture_omp = .FALSE.
    413412    CALL getin('flag_bc_internal_mixture',flag_bc_internal_mixture_omp)
    414413
     
    416415    !Config Key  = new_aod
    417416    !Config Desc = which calcul of aeropt
    418     !Config Def  = false
     417    !Config Def  = FALSE
    419418    !Config Help = Used in physiq.F
    420419    !
    421     new_aod_omp = .true.
     420    new_aod_omp = .TRUE.
    422421    CALL getin('new_aod',new_aod_omp)
    423422
     
    429428    !
    430429    aer_type_omp = 'scenario'
    431     call getin('aer_type', aer_type_omp)
     430    CALL getin('aer_type', aer_type_omp)
    432431
    433432    !
    434433    !Config Key  = bl95_b0
    435434    !Config Desc = Parameter in CDNC-maer link (Boucher&Lohmann 1995)
    436     !Config Def  = .false.
     435    !Config Def  = .FALSE.
    437436    !Config Help = Used in nuage.F
    438437    !
    439438    bl95_b0_omp = 2.
    440     call getin('bl95_b0', bl95_b0_omp)
     439    CALL getin('bl95_b0', bl95_b0_omp)
    441440
    442441    !Config Key  = bl95_b1
    443442    !Config Desc = Parameter in CDNC-maer link (Boucher&Lohmann 1995)
    444     !Config Def  = .false.
     443    !Config Def  = .FALSE.
    445444    !Config Help = Used in nuage.F
    446445    !
    447446    bl95_b1_omp = 0.2
    448     call getin('bl95_b1', bl95_b1_omp)
     447    CALL getin('bl95_b1', bl95_b1_omp)
    449448
    450449    !Config Key  = freq_ISCCP
     
    455454    !
    456455    freq_ISCCP_omp = 10800.
    457     call getin('freq_ISCCP', freq_ISCCP_omp)
     456    CALL getin('freq_ISCCP', freq_ISCCP_omp)
    458457    !
    459458    !Config Key  = ecrit_ISCCP
     
    465464    !
    466465    ecrit_ISCCP_omp = 1.
    467     call getin('ecrit_ISCCP', ecrit_ISCCP_omp)
     466    CALL getin('ecrit_ISCCP', ecrit_ISCCP_omp)
    468467
    469468    !Config Key  = freq_COSP
     
    474473    !
    475474    freq_COSP_omp = 10800.
    476     call getin('freq_COSP', freq_COSP_omp)
     475    CALL getin('freq_COSP', freq_COSP_omp)
    477476
    478477    !Config Key  = freq_AIRS
     
    483482    !
    484483    freq_AIRS_omp = 10800.
    485     call getin('freq_AIRS', freq_AIRS_omp)
     484    CALL getin('freq_AIRS', freq_AIRS_omp)
    486485
    487486    !
     
    492491    !               
    493492    ip_ebil_phy_omp = 0
    494     call getin('ip_ebil_phy', ip_ebil_phy_omp)
     493    CALL getin('ip_ebil_phy', ip_ebil_phy_omp)
    495494    !
    496495    !Config Key  = seuil_inversion
     
    500499    !               
    501500    seuil_inversion_omp = -0.1
    502     call getin('seuil_inversion', seuil_inversion_omp)
     501    CALL getin('seuil_inversion', seuil_inversion_omp)
    503502
    504503    !
     
    512511    !valeur AMIP II
    513512    R_ecc_omp = 0.016715
    514     call getin('R_ecc', R_ecc_omp)
     513    CALL getin('R_ecc', R_ecc_omp)
    515514    !
    516515    !Config Key  = R_peri
     
    522521    !valeur AMIP II
    523522    R_peri_omp = 102.7
    524     call getin('R_peri', R_peri_omp)
     523    CALL getin('R_peri', R_peri_omp)
    525524    !
    526525    !Config Key  = R_incl
     
    532531    !valeur AMIP II
    533532    R_incl_omp = 23.441
    534     call getin('R_incl', R_incl_omp)
     533    CALL getin('R_incl', R_incl_omp)
    535534    !
    536535    !Config Key  = solaire
     
    542541    !valeur AMIP II
    543542    solaire_omp = 1365.
    544     call getin('solaire', solaire_omp)
     543    CALL getin('solaire', solaire_omp)
    545544    !
    546545    !Config Key  = ok_sun_time
    547546    !Config Desc = oui ou non variabilite solaire
    548     !Config Def  = .false.
     547    !Config Def  = .FALSE.
    549548    !Config Help =
    550549    !
    551550    !
    552551    !valeur AMIP II
    553     ok_suntime_rrtm_omp = .false.
    554     call getin('ok_suntime_rrtm',ok_suntime_rrtm_omp)
     552    ok_suntime_rrtm_omp = .FALSE.
     553    CALL getin('ok_suntime_rrtm',ok_suntime_rrtm_omp)
    555554    !
    556555    !Config Key  = co2_ppm
     
    562561    !valeur AMIP II
    563562    co2_ppm_omp = 348.
    564     call getin('co2_ppm', co2_ppm_omp)
     563    CALL getin('co2_ppm', co2_ppm_omp)
    565564    !
    566565    !Config Key  = RCO2
     
    574573    RCO2_omp = co2_ppm_omp * 1.0e-06  * 44.011/28.97 ! pour co2_ppm=348.
    575574
    576     !  call getin('RCO2', RCO2)
     575    !  CALL getin('RCO2', RCO2)
    577576    !
    578577    !Config Key  = RCH4
     
    588587    !ancienne valeur
    589588    ! RCH4 = 1.72E-06* 16.043/28.97
    590     !OK call getin('RCH4', RCH4)
     589    !OK CALL getin('RCH4', RCH4)
    591590    zzz = 1650.
    592     call getin('CH4_ppb', zzz)
     591    CALL getin('CH4_ppb', zzz)
    593592    CH4_ppb_omp = zzz
    594593    RCH4_omp = CH4_ppb_omp * 1.0E-09 * 16.043/28.97
     
    606605    !ancienne valeur
    607606    ! RN2O = 310.E-09* 44.013/28.97
    608     !OK  call getin('RN2O', RN2O)
     607    !OK  CALL getin('RN2O', RN2O)
    609608    zzz=306.
    610     call getin('N2O_ppb', zzz)
     609    CALL getin('N2O_ppb', zzz)
    611610    N2O_ppb_omp = zzz
    612611    RN2O_omp = N2O_ppb_omp * 1.0E-09 * 44.013/28.97
     
    620619    !OK RCFC11 = 280.E-12* 137.3686/28.97
    621620    zzz = 280.
    622     call getin('CFC11_ppt',zzz)
     621    CALL getin('CFC11_ppt',zzz)
    623622    CFC11_ppt_omp = zzz
    624623    RCFC11_omp=CFC11_ppt_omp* 1.0E-12 * 137.3686/28.97
    625624    ! RCFC11 = 1.327690990680013E-09
    626     !OK call getin('RCFC11', RCFC11)
     625    !OK CALL getin('RCFC11', RCFC11)
    627626    !
    628627    !Config Key  = RCFC12
     
    634633    !OK RCFC12 = 484.E-12* 120.9140/28.97
    635634    zzz = 484.
    636     call getin('CFC12_ppt',zzz)
     635    CALL getin('CFC12_ppt',zzz)
    637636    CFC12_ppt_omp = zzz
    638637    RCFC12_omp = CFC12_ppt_omp * 1.0E-12 * 120.9140/28.97
    639638    ! RCFC12 = 2.020102726958923E-09
    640     !OK call getin('RCFC12', RCFC12)
     639    !OK CALL getin('RCFC12', RCFC12)
    641640
    642641    !ajout CFMIP begin
     
    648647    !               
    649648    co2_ppm_per_omp = co2_ppm_omp
    650     call getin('co2_ppm_per', co2_ppm_per_omp)
     649    CALL getin('co2_ppm_per', co2_ppm_per_omp)
    651650    !
    652651    !Config Key  = RCO2_per
     
    660659    !Config Key  = ok_4xCO2atm
    661660    !Config Desc = Calcul ou non effet radiatif 4xco2
    662     !Config Def  = .false.
    663     !Config Help =
    664 
    665     ok_4xCO2atm_omp = .false.
    666     call getin('ok_4xCO2atm',ok_4xCO2atm_omp)
     661    !Config Def  = .FALSE.
     662    !Config Help =
     663
     664    ok_4xCO2atm_omp = .FALSE.
     665    CALL getin('ok_4xCO2atm',ok_4xCO2atm_omp)
    667666
    668667    !Config Key  = RCH4_per
     
    672671    !               
    673672    zzz = CH4_ppb_omp
    674     call getin('CH4_ppb_per', zzz)
     673    CALL getin('CH4_ppb_per', zzz)
    675674    CH4_ppb_per_omp = zzz
    676675    RCH4_per_omp = CH4_ppb_per_omp * 1.0E-09 * 16.043/28.97
     
    682681    !               
    683682    zzz = N2O_ppb_omp
    684     call getin('N2O_ppb_per', zzz)
     683    CALL getin('N2O_ppb_per', zzz)
    685684    N2O_ppb_per_omp = zzz
    686685    RN2O_per_omp = N2O_ppb_per_omp * 1.0E-09 * 44.013/28.97
     
    692691    !               
    693692    zzz = CFC11_ppt_omp
    694     call getin('CFC11_ppt_per',zzz)
     693    CALL getin('CFC11_ppt_per',zzz)
    695694    CFC11_ppt_per_omp = zzz
    696695    RCFC11_per_omp=CFC11_ppt_per_omp* 1.0E-12 * 137.3686/28.97
     
    702701    !               
    703702    zzz = CFC12_ppt_omp
    704     call getin('CFC12_ppt_per',zzz)
     703    CALL getin('CFC12_ppt_per',zzz)
    705704    CFC12_ppt_per_omp = zzz
    706705    RCFC12_per_omp = CFC12_ppt_per_omp * 1.0E-12 * 120.9140/28.97
     
    851850    !
    852851    epmax_omp = .993
    853     call getin('epmax', epmax_omp)
     852    CALL getin('epmax', epmax_omp)
    854853
    855854    coef_epmax_cape_omp = 0.0   
    856     call getin('coef_epmax_cape', coef_epmax_cape_omp)       
     855    CALL getin('coef_epmax_cape', coef_epmax_cape_omp)       
    857856    !
    858857    !Config Key  = ok_adj_ema
    859858    !Config Desc = 
    860     !Config Def  = false
    861     !Config Help =
    862     !
    863     ok_adj_ema_omp = .false.
    864     call getin('ok_adj_ema',ok_adj_ema_omp)
     859    !Config Def  = FALSE
     860    !Config Help =
     861    !
     862    ok_adj_ema_omp = .FALSE.
     863    CALL getin('ok_adj_ema',ok_adj_ema_omp)
    865864    !
    866865    !Config Key  = iflag_clw
     
    870869    !
    871870    iflag_clw_omp = 0
    872     call getin('iflag_clw',iflag_clw_omp)
     871    CALL getin('iflag_clw',iflag_clw_omp)
    873872    !
    874873    !Config Key  = cld_lc_lsc
     
    878877    !
    879878    cld_lc_lsc_omp = 2.6e-4
    880     call getin('cld_lc_lsc',cld_lc_lsc_omp)
     879    CALL getin('cld_lc_lsc',cld_lc_lsc_omp)
    881880    !
    882881    !Config Key  = cld_lc_con
     
    886885    !
    887886    cld_lc_con_omp = 2.6e-4
    888     call getin('cld_lc_con',cld_lc_con_omp)
     887    CALL getin('cld_lc_con',cld_lc_con_omp)
    889888    !
    890889    !Config Key  = cld_tau_lsc
     
    894893    !
    895894    cld_tau_lsc_omp = 3600.
    896     call getin('cld_tau_lsc',cld_tau_lsc_omp)
     895    CALL getin('cld_tau_lsc',cld_tau_lsc_omp)
    897896    !
    898897    !Config Key  = cld_tau_con
     
    902901    !
    903902    cld_tau_con_omp = 3600.
    904     call getin('cld_tau_con',cld_tau_con_omp)
     903    CALL getin('cld_tau_con',cld_tau_con_omp)
    905904    !
    906905    !Config Key  = ffallv_lsc
     
    910909    !
    911910    ffallv_lsc_omp = 1.
    912     call getin('ffallv_lsc',ffallv_lsc_omp)
     911    CALL getin('ffallv_lsc',ffallv_lsc_omp)
    913912    !
    914913    !Config Key  = ffallv_con
     
    918917    !
    919918    ffallv_con_omp = 1.
    920     call getin('ffallv_con',ffallv_con_omp)
     919    CALL getin('ffallv_con',ffallv_con_omp)
    921920    !
    922921    !Config Key  = coef_eva
     
    926925    !
    927926    coef_eva_omp = 2.e-5
    928     call getin('coef_eva',coef_eva_omp)
     927    CALL getin('coef_eva',coef_eva_omp)
    929928    !
    930929    !Config Key  = reevap_ice
    931930    !Config Desc = 
    932     !Config Def  = .false.
    933     !Config Help =
    934     !
    935     reevap_ice_omp = .false.
    936     call getin('reevap_ice',reevap_ice_omp)
     931    !Config Def  = .FALSE.
     932    !Config Help =
     933    !
     934    reevap_ice_omp = .FALSE.
     935    CALL getin('reevap_ice',reevap_ice_omp)
    937936
    938937    !Config Key  = iflag_ratqs
     
    942941    !
    943942    iflag_ratqs_omp = 1
    944     call getin('iflag_ratqs',iflag_ratqs_omp)
     943    CALL getin('iflag_ratqs',iflag_ratqs_omp)
    945944
    946945    !
     
    951950    !
    952951    iflag_radia_omp = 1
    953     call getin('iflag_radia',iflag_radia_omp)
     952    CALL getin('iflag_radia',iflag_radia_omp)
    954953
    955954    !
     
    960959    !
    961960    iflag_rrtm_omp = 0
    962     call getin('iflag_rrtm',iflag_rrtm_omp)
     961    CALL getin('iflag_rrtm',iflag_rrtm_omp)
    963962
    964963    !
     
    969968    !
    970969    NSW_omp = 2
    971     call getin('NSW',NSW_omp)
     970    CALL getin('NSW',NSW_omp)
    972971    !albedo SB >>>
    973972    iflag_albedo_omp = 0
    974     call getin('iflag_albedo',iflag_albedo_omp)
    975 
    976     ok_chlorophyll_omp=.false.
    977     call getin('ok_chlorophyll',ok_chlorophyll_omp)
     973    CALL getin('iflag_albedo',iflag_albedo_omp)
     974
     975    ok_chlorophyll_omp=.FALSE.
     976    CALL getin('ok_chlorophyll',ok_chlorophyll_omp)
    978977    !albedo SB <<<
    979978
     
    988987    ! pour assurer une retrocompatiblite.
    989988    ! A abandonner un jour
    990     call getin('iflag_cldcon',iflag_cld_th_omp)
    991     call getin('iflag_cld_th',iflag_cld_th_omp)
     989    CALL getin('iflag_cldcon',iflag_cld_th_omp)
     990    CALL getin('iflag_cld_th',iflag_cld_th_omp)
    992991    iflag_cld_cv_omp = 0
    993     call getin('iflag_cld_cv',iflag_cld_cv_omp)
     992    CALL getin('iflag_cld_cv',iflag_cld_cv_omp)
    994993
    995994    !
     
    1000999    !
    10011000    tau_cld_cv_omp = 10.
    1002     call getin('tau_cld_cv',tau_cld_cv_omp)
     1001    CALL getin('tau_cld_cv',tau_cld_cv_omp)
    10031002
    10041003    !
     
    10091008    !
    10101009    coefw_cld_cv_omp = 0.1
    1011     call getin('coefw_cld_cv',coefw_cld_cv_omp)
     1010    CALL getin('coefw_cld_cv',coefw_cld_cv_omp)
    10121011
    10131012
     
    10211020    !
    10221021    iflag_pdf_omp = 0
    1023     call getin('iflag_pdf',iflag_pdf_omp)
     1022    CALL getin('iflag_pdf',iflag_pdf_omp)
    10241023    !
    10251024    !Config Key  = fact_cldcon
     
    10291028    !
    10301029    fact_cldcon_omp = 0.375
    1031     call getin('fact_cldcon',fact_cldcon_omp)
     1030    CALL getin('fact_cldcon',fact_cldcon_omp)
    10321031
    10331032    !
     
    10381037    !
    10391038    facttemps_omp = 1.e-4
    1040     call getin('facttemps',facttemps_omp)
     1039    CALL getin('facttemps',facttemps_omp)
    10411040
    10421041    !
    10431042    !Config Key  = ok_newmicro
    10441043    !Config Desc = 
    1045     !Config Def  = .true.
    1046     !Config Help =
    1047     !
    1048     ok_newmicro_omp = .true.
    1049     call getin('ok_newmicro',ok_newmicro_omp)
     1044    !Config Def  = .TRUE.
     1045    !Config Help =
     1046    !
     1047    ok_newmicro_omp = .TRUE.
     1048    CALL getin('ok_newmicro',ok_newmicro_omp)
    10501049    !
    10511050    !Config Key  = ratqsbas
     
    10551054    !
    10561055    ratqsbas_omp = 0.01
    1057     call getin('ratqsbas',ratqsbas_omp)
     1056    CALL getin('ratqsbas',ratqsbas_omp)
    10581057    !
    10591058    !Config Key  = ratqshaut
     
    10631062    !
    10641063    ratqshaut_omp = 0.3
    1065     call getin('ratqshaut',ratqshaut_omp)
     1064    CALL getin('ratqshaut',ratqshaut_omp)
    10661065
    10671066    !Config Key  = tau_ratqs
     
    10711070    !
    10721071    tau_ratqs_omp = 1800.
    1073     call getin('tau_ratqs',tau_ratqs_omp)
     1072    CALL getin('tau_ratqs',tau_ratqs_omp)
    10741073
    10751074    !
     
    10831082    !
    10841083    solarlong0_omp = -999.999
    1085     call getin('solarlong0',solarlong0_omp)
     1084    CALL getin('solarlong0',solarlong0_omp)
    10861085    !
    10871086    !-----------------------------------------------------------------------
     
    10901089    ! Default value -1 to activate the full computation
    10911090    qsol0_omp = -1.
    1092     call getin('qsol0',qsol0_omp)
     1091    CALL getin('qsol0',qsol0_omp)
    10931092    evap0_omp = -1.
    1094     call getin('evap0',evap0_omp)
     1093    CALL getin('evap0',evap0_omp)
    10951094    albsno0_omp = -1.
    1096     call getin('albsno0',albsno0_omp)
     1095    CALL getin('albsno0',albsno0_omp)
    10971096    !
    10981097    !-----------------------------------------------------------------------
     
    11041103    !
    11051104    inertie_ice_omp = 2000.
    1106     call getin('inertie_ice',inertie_ice_omp)
     1105    CALL getin('inertie_ice',inertie_ice_omp)
    11071106    !
    11081107    !Config Key  = inertie_sno
     
    11121111    !
    11131112    inertie_sno_omp = 2000.
    1114     call getin('inertie_sno',inertie_sno_omp)
     1113    CALL getin('inertie_sno',inertie_sno_omp)
    11151114    !
    11161115    !Config Key  = inertie_sol
     
    11201119    !
    11211120    inertie_sol_omp = 2000.
    1122     call getin('inertie_sol',inertie_sol_omp)
     1121    CALL getin('inertie_sol',inertie_sol_omp)
    11231122
    11241123    !
     
    11291128    !
    11301129    rad_froid_omp = 35.0
    1131     call getin('rad_froid',rad_froid_omp)
     1130    CALL getin('rad_froid',rad_froid_omp)
    11321131
    11331132    !
     
    11381137    !
    11391138    rad_chau1_omp = 13.0
    1140     call getin('rad_chau1',rad_chau1_omp)
     1139    CALL getin('rad_chau1',rad_chau1_omp)
    11411140
    11421141    !
     
    11471146    !
    11481147    rad_chau2_omp = 9.0
    1149     call getin('rad_chau2',rad_chau2_omp)
     1148    CALL getin('rad_chau2',rad_chau2_omp)
    11501149
    11511150    !
     
    11561155    !
    11571156    t_glace_min_omp = 258.
    1158     call getin('t_glace_min',t_glace_min_omp)
     1157    CALL getin('t_glace_min',t_glace_min_omp)
    11591158
    11601159    !
     
    11651164    !
    11661165    t_glace_max_omp = 273.13
    1167     call getin('t_glace_max',t_glace_max_omp)
     1166    CALL getin('t_glace_max',t_glace_max_omp)
    11681167
    11691168    !
     
    11741173    !
    11751174    exposant_glace_omp = 1.
    1176     call getin('exposant_glace',exposant_glace_omp)
     1175    CALL getin('exposant_glace',exposant_glace_omp)
    11771176
    11781177    !
     
    11831182    !
    11841183    iflag_t_glace_omp = 0
    1185     call getin('iflag_t_glace',iflag_t_glace_omp)
     1184    CALL getin('iflag_t_glace',iflag_t_glace_omp)
    11861185
    11871186    !
     
    11921191    !
    11931192    iflag_cloudth_vert_omp = 0
    1194     call getin('iflag_cloudth_vert',iflag_cloudth_vert_omp)
     1193    CALL getin('iflag_cloudth_vert',iflag_cloudth_vert_omp)
    11951194
    11961195    !
     
    12011200    !
    12021201    iflag_ice_thermo_omp = 0
    1203     call getin('iflag_ice_thermo',iflag_ice_thermo_omp)
     1202    CALL getin('iflag_ice_thermo',iflag_ice_thermo_omp)
    12041203
    12051204    !Config Key  = rei_min
     
    12091208    !
    12101209    rei_min_omp = 3.5
    1211     call getin('rei_min',rei_min_omp)
     1210    CALL getin('rei_min',rei_min_omp)
    12121211
    12131212    !
     
    12181217    !
    12191218    rei_max_omp = 61.29
    1220     call getin('rei_max',rei_max_omp)
     1219    CALL getin('rei_max',rei_max_omp)
    12211220
    12221221    !
     
    12271226    !
    12281227    top_height_omp = 3
    1229     call getin('top_height',top_height_omp)
     1228    CALL getin('top_height',top_height_omp)
    12301229
    12311230    !
     
    12361235    !
    12371236    overlap_omp = 3
    1238     call getin('overlap',overlap_omp)
    1239 
    1240 
    1241     !
     1237    CALL getin('overlap',overlap_omp)
     1238
    12421239    !
    12431240    !Config Key  = cdmmax
     
    12471244    !
    12481245    cdmmax_omp = 1.3E-3
    1249     call getin('cdmmax',cdmmax_omp)
     1246    CALL getin('cdmmax',cdmmax_omp)
    12501247
    12511248    !
     
    12561253    !
    12571254    cdhmax_omp = 1.1E-3
    1258     call getin('cdhmax',cdhmax_omp)
     1255    CALL getin('cdhmax',cdhmax_omp)
    12591256
    12601257    !261103
     
    12661263    !
    12671264    ksta_omp = 1.0e-10
    1268     call getin('ksta',ksta_omp)
     1265    CALL getin('ksta',ksta_omp)
    12691266
    12701267    !
     
    12751272    !
    12761273    ksta_ter_omp = 1.0e-10
    1277     call getin('ksta_ter',ksta_ter_omp)
     1274    CALL getin('ksta_ter',ksta_ter_omp)
    12781275
    12791276    !Config Key  = f_ri_cd_min
     
    12831280    !
    12841281    f_ri_cd_min_omp = 0.1
    1285     call getin('f_ri_cd_min',f_ri_cd_min_omp)
     1282    CALL getin('f_ri_cd_min',f_ri_cd_min_omp)
    12861283
    12871284    !
    12881285    !Config Key  = ok_kzmin
    12891286    !Config Desc =
    1290     !Config Def  = .true.
    1291     !Config Help =
    1292     !
    1293     ok_kzmin_omp = .true.
    1294     call getin('ok_kzmin',ok_kzmin_omp)
     1287    !Config Def  = .TRUE.
     1288    !Config Help =
     1289    !
     1290    ok_kzmin_omp = .TRUE.
     1291    CALL getin('ok_kzmin',ok_kzmin_omp)
    12951292
    12961293    pbl_lmixmin_alpha_omp=0.0
    1297     call getin('pbl_lmixmin_alpha',pbl_lmixmin_alpha_omp)
    1298 
     1294    CALL getin('pbl_lmixmin_alpha',pbl_lmixmin_alpha_omp)
    12991295
    13001296    !
     
    13051301    !
    13061302    fmagic_omp = 1.
    1307     call getin('fmagic',fmagic_omp)
     1303    CALL getin('fmagic',fmagic_omp)
    13081304
    13091305    !
     
    13141310    !
    13151311    pmagic_omp = 0.
    1316     call getin('pmagic',pmagic_omp)
     1312    CALL getin('pmagic',pmagic_omp)
    13171313
    13181314
    13191315    !Config Key = ok_lic_melt
    13201316    !Config Desc = Prise en compte de la fonte de la calotte dans le bilan d'eau
    1321     !Config Def  = .false.
    1322     !Config Help = mettre a .false. pour assurer la conservation en eau
    1323     ok_lic_melt_omp = .false.
    1324     call getin('ok_lic_melt', ok_lic_melt_omp)
     1317    !Config Def  = .FALSE.
     1318    !Config Help = mettre a .FALSE. pour assurer la conservation en eau
     1319    ok_lic_melt_omp = .FALSE.
     1320    CALL getin('ok_lic_melt', ok_lic_melt_omp)
    13251321
    13261322    !
     
    13341330    !
    13351331    iflag_pbl_omp = 1
    1336     call getin('iflag_pbl',iflag_pbl_omp)
     1332    CALL getin('iflag_pbl',iflag_pbl_omp)
    13371333    !
    13381334    !Config Key  = iflag_pbl_split
     
    13421338    !
    13431339    iflag_pbl_split_omp = 0
    1344     call getin('iflag_pbl_split',iflag_pbl_split_omp)
     1340    CALL getin('iflag_pbl_split',iflag_pbl_split_omp)
    13451341    !
    13461342    !Config Key  = iflag_order2_sollw
     
    13501346    !
    13511347    iflag_order2_sollw_omp = 0
    1352     call getin('iflag_order2_sollw',iflag_order2_sollw_omp)
     1348    CALL getin('iflag_order2_sollw',iflag_order2_sollw_omp)
    13531349    !
    13541350    !Config Key  = iflag_thermals
     
    13581354    !
    13591355    iflag_thermals_omp = 0
    1360     call getin('iflag_thermals',iflag_thermals_omp)
     1356    CALL getin('iflag_thermals',iflag_thermals_omp)
    13611357    !
    13621358    !Config Key  = iflag_thermals_ed
     
    13671363    fact_thermals_ed_dz_omp = 0.1
    13681364
    1369     call getin('fact_thermals_ed_dz',fact_thermals_ed_dz_omp)
     1365    CALL getin('fact_thermals_ed_dz',fact_thermals_ed_dz_omp)
    13701366    !
    13711367    !
     
    13761372    !
    13771373    iflag_thermals_ed_omp = 0
    1378     call getin('iflag_thermals_ed',iflag_thermals_ed_omp)
     1374    CALL getin('iflag_thermals_ed',iflag_thermals_ed_omp)
    13791375    !
    13801376    !
     
    13851381    !
    13861382    iflag_thermals_optflux_omp = 0
    1387     call getin('iflag_thermals_optflux',iflag_thermals_optflux_omp)
     1383    CALL getin('iflag_thermals_optflux',iflag_thermals_optflux_omp)
    13881384    !
    13891385    !Config Key  = iflag_thermals_closure
     
    13931389    !
    13941390    iflag_thermals_closure_omp = 1
    1395     call getin('iflag_thermals_closure',iflag_thermals_closure_omp)
    1396     !
    1397     !
    1398     !
     1391    CALL getin('iflag_thermals_closure',iflag_thermals_closure_omp)
    13991392    !
    14001393    !Config Key  = nsplit_thermals
     
    14041397    !
    14051398    nsplit_thermals_omp = 1
    1406     call getin('nsplit_thermals',nsplit_thermals_omp)
     1399    CALL getin('nsplit_thermals',nsplit_thermals_omp)
    14071400
    14081401    !Config Key  = alp_bl_k
     
    14121405    !
    14131406    alp_bl_k_omp = 1.
    1414     call getin('alp_bl_k',alp_bl_k_omp)
     1407    CALL getin('alp_bl_k',alp_bl_k_omp)
    14151408
    14161409    ! nrlmd le 10/04/2012
     
    14221415    !
    14231416    iflag_trig_bl_omp = 0
    1424     call getin('iflag_trig_bl',iflag_trig_bl_omp)
     1417    CALL getin('iflag_trig_bl',iflag_trig_bl_omp)
    14251418
    14261419    !Config Key  = s_trig_bl
     
    14301423    !
    14311424    s_trig_omp = 2e7
    1432     call getin('s_trig',s_trig_omp)
     1425    CALL getin('s_trig',s_trig_omp)
    14331426
    14341427    !Config Key  = tau_trig_shallow
     
    14381431    !
    14391432    tau_trig_shallow_omp = 600
    1440     call getin('tau_trig_shallow',tau_trig_shallow_omp)
     1433    CALL getin('tau_trig_shallow',tau_trig_shallow_omp)
    14411434
    14421435    !Config Key  = tau_trig_deep
     
    14461439    !
    14471440    tau_trig_deep_omp = 1800
    1448     call getin('tau_trig_deep',tau_trig_deep_omp)
     1441    CALL getin('tau_trig_deep',tau_trig_deep_omp)
    14491442
    14501443    !Config Key  = iflag_clos_bl
     
    14541447    !
    14551448    iflag_clos_bl_omp = 0
    1456     call getin('iflag_clos_bl',iflag_clos_bl_omp)
     1449    CALL getin('iflag_clos_bl',iflag_clos_bl_omp)
    14571450
    14581451    ! fin nrlmd le 10/04/2012
     
    14651458    !
    14661459    tau_thermals_omp = 0.
    1467     call getin('tau_thermals',tau_thermals_omp)
     1460    CALL getin('tau_thermals',tau_thermals_omp)
    14681461
    14691462    !
     
    14741467    !
    14751468    iflag_coupl_omp = 0
    1476     call getin('iflag_coupl',iflag_coupl_omp)
     1469    CALL getin('iflag_coupl',iflag_coupl_omp)
    14771470
    14781471    !
     
    14831476    !
    14841477    iflag_clos_omp = 1
    1485     call getin('iflag_clos',iflag_clos_omp)
     1478    CALL getin('iflag_clos',iflag_clos_omp)
    14861479    !
    14871480    !Config Key  = coef_clos_ls
     
    14911484    !
    14921485    coef_clos_ls_omp = 0.
    1493     call getin('coef_clos_ls',coef_clos_ls_omp)
     1486    CALL getin('coef_clos_ls',coef_clos_ls_omp)
    14941487
    14951488    !
     
    15001493    !
    15011494    iflag_cvl_sigd_omp = 0
    1502     call getin('iflag_cvl_sigd',iflag_cvl_sigd_omp)
     1495    CALL getin('iflag_cvl_sigd',iflag_cvl_sigd_omp)
    15031496
    15041497    !Config Key  = iflag_wake
     
    15081501    !
    15091502    iflag_wake_omp = 0
    1510     call getin('iflag_wake',iflag_wake_omp)
     1503    CALL getin('iflag_wake',iflag_wake_omp)
    15111504
    15121505    !Config Key  = alp_offset
     
    15161509    !
    15171510    alp_offset_omp = 0.
    1518     call getin('alp_offset',alp_offset_omp)
     1511    CALL getin('alp_offset',alp_offset_omp)
    15191512
    15201513    !
     
    15251518    !
    15261519    lev_histhf_omp = 1
    1527     call getin('lev_histhf',lev_histhf_omp)
     1520    CALL getin('lev_histhf',lev_histhf_omp)
    15281521
    15291522    !
     
    15341527    !
    15351528    lev_histday_omp = 1
    1536     call getin('lev_histday',lev_histday_omp)
     1529    CALL getin('lev_histday',lev_histday_omp)
    15371530
    15381531    !
     
    15431536    !
    15441537    lev_histmth_omp = 2
    1545     call getin('lev_histmth',lev_histmth_omp)
     1538    CALL getin('lev_histmth',lev_histmth_omp)
    15461539    !
    15471540    !Config Key  = lev_histins
     
    15511544    !
    15521545    lev_histins_omp = 1
    1553     call getin('lev_histins',lev_histins_omp)
     1546    CALL getin('lev_histins',lev_histins_omp)
    15541547    !
    15551548    !Config Key  = lev_histLES
     
    15591552    !
    15601553    lev_histLES_omp = 1
    1561     call getin('lev_histLES',lev_histLES_omp)
     1554    CALL getin('lev_histLES',lev_histLES_omp)
    15621555    !
    15631556    !Config Key  = lev_histdayNMC
     
    15671560    !
    15681561    lev_histdayNMC_omp = 8
    1569     call getin('lev_histdayNMC',lev_histdayNMC_omp)
     1562    CALL getin('lev_histdayNMC',lev_histdayNMC_omp)
    15701563    !
    15711564    !Config Key  = levout_histNMC
     
    15771570    levout_histNMC_omp(2) = 5
    15781571    levout_histNMC_omp(3) = 5
    1579     call getin('levout_histNMC',levout_histNMC_omp)
     1572    CALL getin('levout_histNMC',levout_histNMC_omp)
    15801573    !
    15811574    !histNMC BEG
     
    15871580    !Config Help =
    15881581    !
    1589     ok_histNMC_omp(1) = .false.
    1590     ok_histNMC_omp(2) = .false.
    1591     ok_histNMC_omp(3) = .false.
    1592     call getin('ok_histNMC',ok_histNMC_omp)
     1582    ok_histNMC_omp(1) = .FALSE.
     1583    ok_histNMC_omp(2) = .FALSE.
     1584    ok_histNMC_omp(3) = .FALSE.
     1585    CALL getin('ok_histNMC',ok_histNMC_omp)
    15931586    !
    15941587    !Config Key  = freq_outNMC
     
    16021595    freq_outNMC_omp(2) = 1.
    16031596    freq_outNMC_omp(3) = 1./4.
    1604     call getin('freq_outNMC',freq_outNMC_omp)
     1597    CALL getin('freq_outNMC',freq_outNMC_omp)
    16051598    !
    16061599    !Config Key  = freq_calNMC
     
    16141607    freq_calNMC_omp(2) = pasphys
    16151608    freq_calNMC_omp(3) = pasphys
    1616     call getin('freq_calNMC',freq_calNMC_omp)
     1609    CALL getin('freq_calNMC',freq_calNMC_omp)
    16171610    !
    16181611    !Config Key  = type_run
     
    16221615    !
    16231616    type_run_omp = 'AMIP'
    1624     call getin('type_run',type_run_omp)
     1617    CALL getin('type_run',type_run_omp)
    16251618
    16261619    !
    16271620    !Config Key  = ok_cosp
    16281621    !Config Desc =
    1629     !Config Def  = .false.
    1630     !Config Help =
    1631     !
    1632     ok_cosp_omp = .false.
    1633     call getin('ok_cosp',ok_cosp_omp)
     1622    !Config Def  = .FALSE.
     1623    !Config Help =
     1624    !
     1625    ok_cosp_omp = .FALSE.
     1626    CALL getin('ok_cosp',ok_cosp_omp)
    16341627
    16351628    !
    16361629    !Config Key  = ok_airs
    16371630    !Config Desc =
    1638     !Config Def  = .false.
    1639     !Config Help =
    1640     !
    1641     ok_airs_omp = .false.
    1642     call getin('ok_airs',ok_airs_omp)
     1631    !Config Def  = .FALSE.
     1632    !Config Help =
     1633    !
     1634    ok_airs_omp = .FALSE.
     1635    CALL getin('ok_airs',ok_airs_omp)
    16431636
    16441637    !
    16451638    !Config Key  = ok_mensuelCOSP
    16461639    !Config Desc =
    1647     !Config Def  = .true.
    1648     !Config Help =
    1649     !
    1650     ok_mensuelCOSP_omp = .true.
    1651     call getin('ok_mensuelCOSP',ok_mensuelCOSP_omp)
     1640    !Config Def  = .TRUE.
     1641    !Config Help =
     1642    !
     1643    ok_mensuelCOSP_omp = .TRUE.
     1644    CALL getin('ok_mensuelCOSP',ok_mensuelCOSP_omp)
    16521645
    16531646    !
    16541647    !Config Key  = ok_journeCOSP
    16551648    !Config Desc =
    1656     !Config Def  = .true.
    1657     !Config Help =
    1658     !
    1659     ok_journeCOSP_omp = .true.
    1660     call getin('ok_journeCOSP',ok_journeCOSP_omp)
     1649    !Config Def  = .TRUE.
     1650    !Config Help =
     1651    !
     1652    ok_journeCOSP_omp = .TRUE.
     1653    CALL getin('ok_journeCOSP',ok_journeCOSP_omp)
    16611654
    16621655    !
    16631656    !Config Key  = ok_hfCOSP
    16641657    !Config Desc =
    1665     !Config Def  = .false.
    1666     !Config Help =
    1667     !
    1668     ok_hfCOSP_omp = .false.
    1669     call getin('ok_hfCOSP',ok_hfCOSP_omp)
     1658    !Config Def  = .FALSE.
     1659    !Config Help =
     1660    !
     1661    ok_hfCOSP_omp = .FALSE.
     1662    CALL getin('ok_hfCOSP',ok_hfCOSP_omp)
    16701663
    16711664    !
     
    16791672    !
    16801673    lonmin_ins_omp = 100.
    1681     call getin('lonmin_ins',lonmin_ins_omp)
     1674    CALL getin('lonmin_ins',lonmin_ins_omp)
    16821675    !
    16831676    !Config Key  = lonmax_ins
     
    16871680    !
    16881681    lonmax_ins_omp = 130.
    1689     call getin('lonmax_ins',lonmax_ins_omp)
     1682    CALL getin('lonmax_ins',lonmax_ins_omp)
    16901683    !
    16911684    !Config Key  = latmin_ins
     
    16951688    !
    16961689    latmin_ins_omp = -20.
    1697     call getin('latmin_ins',latmin_ins_omp)
     1690    CALL getin('latmin_ins',latmin_ins_omp)
    16981691    !
    16991692    !Config Key  = latmax_ins
     
    17031696    !
    17041697    latmax_ins_omp = 20.
    1705     call getin('latmax_ins',latmax_ins_omp)
     1698    CALL getin('latmax_ins',latmax_ins_omp)
    17061699    !
    17071700    !Config Key  = ecrit_hf
     
    17111704    !
    17121705    ecrit_hf_omp = 1./8.
    1713     call getin('ecrit_hf',ecrit_hf_omp)
     1706    CALL getin('ecrit_hf',ecrit_hf_omp)
    17141707    !
    17151708    !Config Key  = ecrit_ins
     
    17191712    !
    17201713    ecrit_ins_omp = 1./48.
    1721     call getin('ecrit_ins',ecrit_ins_omp)
     1714    CALL getin('ecrit_ins',ecrit_ins_omp)
    17221715    !
    17231716    !Config Key  = ecrit_day
     
    17271720    !
    17281721    ecrit_day_omp = 1.0
    1729     call getin('ecrit_day',ecrit_day_omp)
     1722    CALL getin('ecrit_day',ecrit_day_omp)
    17301723    !
    17311724    !Config Key  = ecrit_mth
     
    17351728    !
    17361729    ecrit_mth_omp = 30.
    1737     call getin('ecrit_mth',ecrit_mth_omp)
     1730    CALL getin('ecrit_mth',ecrit_mth_omp)
    17381731    !
    17391732    !Config Key  = ecrit_tra
     
    17431736    !
    17441737    ecrit_tra_omp = 0.
    1745     call getin('ecrit_tra',ecrit_tra_omp)
     1738    CALL getin('ecrit_tra',ecrit_tra_omp)
    17461739    !
    17471740    !Config Key  = ecrit_reg
     
    17511744    !
    17521745    ecrit_reg_omp = 0.25   !4 fois par jour
    1753     call getin('ecrit_reg',ecrit_reg_omp)
     1746    CALL getin('ecrit_reg',ecrit_reg_omp)
    17541747    !
    17551748    !
     
    17591752    !
    17601753    f_cdrag_ter_omp = 0.8
    1761     call getin('f_cdrag_ter',f_cdrag_ter_omp)
     1754    CALL getin('f_cdrag_ter',f_cdrag_ter_omp)
    17621755    !
    17631756    f_cdrag_oce_omp = 0.8
    1764     call getin('f_cdrag_oce',f_cdrag_oce_omp)
     1757    CALL getin('f_cdrag_oce',f_cdrag_oce_omp)
    17651758    !
    17661759
    17671760    ! Gustiness flags
    17681761    f_z0qh_oce_omp = 1.
    1769     call getin('f_z0qh_oce',f_z0qh_oce_omp)
     1762    CALL getin('f_z0qh_oce',f_z0qh_oce_omp)
    17701763    !
    17711764    f_qsat_oce_omp = 1.
    1772     call getin('f_qsat_oce',f_qsat_oce_omp)
     1765    CALL getin('f_qsat_oce',f_qsat_oce_omp)
    17731766    !
    17741767    f_gust_bl_omp = 0.
    1775     call getin('f_gust_bl',f_gust_bl_omp)
     1768    CALL getin('f_gust_bl',f_gust_bl_omp)
    17761769    !
    17771770    f_gust_wk_omp = 0.
    1778     call getin('f_gust_wk',f_gust_wk_omp)
     1771    CALL getin('f_gust_wk',f_gust_wk_omp)
    17791772    !
    17801773    !Config Key  = iflag_z0_oce
     
    17841777    !
    17851778    iflag_z0_oce_omp=0
    1786     call getin('iflag_z0_oce',iflag_z0_oce_omp)
     1779    CALL getin('iflag_z0_oce',iflag_z0_oce_omp)
    17871780    !
    17881781    iflag_gusts_omp=0
    1789     call getin('iflag_gusts',iflag_gusts_omp)
     1782    CALL getin('iflag_gusts',iflag_gusts_omp)
    17901783    !
    17911784    min_wind_speed_omp = 1.
    1792     call getin('min_wind_speed',min_wind_speed_omp)
    1793 
    1794     z0m_seaice_omp = 0.002 ; call getin('z0m_seaice',z0m_seaice_omp)
    1795     z0h_seaice_omp = 0.002 ; call getin('z0h_seaice',z0h_seaice_omp)
     1785    CALL getin('min_wind_speed',min_wind_speed_omp)
     1786
     1787    z0m_seaice_omp = 0.002 ; CALL getin('z0m_seaice',z0m_seaice_omp)
     1788    z0h_seaice_omp = 0.002 ; CALL getin('z0h_seaice',z0h_seaice_omp)
    17961789
    17971790    f_rugoro_omp = 0.
    1798     call getin('f_rugoro',f_rugoro_omp)
     1791    CALL getin('f_rugoro',f_rugoro_omp)
    17991792
    18001793    z0min_omp = 0.000015
    1801     call getin('z0min',z0min_omp)
     1794    CALL getin('z0min',z0min_omp)
    18021795
    18031796
     
    18101803    !
    18111804    supcrit1_omp = .540
    1812     call getin('supcrit1',supcrit1_omp)
     1805    CALL getin('supcrit1',supcrit1_omp)
    18131806
    18141807    !
     
    18191812    !
    18201813    supcrit2_omp = .600
    1821     call getin('supcrit2',supcrit2_omp)
     1814    CALL getin('supcrit2',supcrit2_omp)
    18221815
    18231816    !
     
    18341827    !
    18351828    iflag_mix_omp = 1
    1836     call getin('iflag_mix',iflag_mix_omp)
     1829    CALL getin('iflag_mix',iflag_mix_omp)
    18371830
    18381831!
     
    18481841    !
    18491842    iflag_mix_adiab_omp = 0
    1850     call getin('iflag_mix_adiab',iflag_mix_adiab_omp)
     1843    CALL getin('iflag_mix_adiab',iflag_mix_adiab_omp)
    18511844
    18521845    !
     
    18571850    !
    18581851    scut_omp = 0.95
    1859     call getin('scut',scut_omp)
     1852    CALL getin('scut',scut_omp)
    18601853
    18611854    !
     
    18661859    !
    18671860    qqa1_omp = 1.0
    1868     call getin('qqa1',qqa1_omp)
     1861    CALL getin('qqa1',qqa1_omp)
    18691862
    18701863    !
     
    18751868    !
    18761869    qqa2_omp = 0.0
    1877     call getin('qqa2',qqa2_omp)
     1870    CALL getin('qqa2',qqa2_omp)
    18781871
    18791872    !
     
    18841877    !
    18851878    gammas_omp = 0.05
    1886     call getin('gammas',gammas_omp)
     1879    CALL getin('gammas',gammas_omp)
    18871880
    18881881    !
     
    18931886    !
    18941887    Fmax_omp = 0.65
    1895     call getin('Fmax',Fmax_omp)
     1888    CALL getin('Fmax',Fmax_omp)
    18961889
    18971890    !
     
    19021895    !
    19031896    tmax_fonte_cv_omp = 275.15
    1904     call getin('tmax_fonte_cv',tmax_fonte_cv_omp)
     1897    CALL getin('tmax_fonte_cv',tmax_fonte_cv_omp)
    19051898
    19061899    !
     
    19111904    !
    19121905    alphas_omp = -5.
    1913     call getin('alphas',alphas_omp)
     1906    CALL getin('alphas',alphas_omp)
    19141907
    19151908    !Config key = ok_strato
     
    19861979    !Config Key  = OK_LES                                               
    19871980    !Config Desc = Pour des sorties LES                                 
    1988     !Config Def  = .false.                                             
     1981    !Config Def  = .FALSE.                                             
    19891982    !Config Help = Pour creer le fichier histLES contenant les sorties 
    19901983    !              LES                                                 
    19911984    !                                                                   
    1992     ok_LES_omp = .false.                                             
    1993     call getin('OK_LES', ok_LES_omp)                                 
     1985    ok_LES_omp = .FALSE.                                             
     1986    CALL getin('OK_LES', ok_LES_omp)                                 
    19941987
    19951988    !Config Key  = callstats                                               
    19961989    !Config Desc = Pour des sorties callstats                                 
    1997     !Config Def  = .false.                                             
     1990    !Config Def  = .FALSE.                                             
    19981991    !Config Help = Pour creer le fichier stats contenant les sorties 
    19991992    !              stats                                                 
    20001993    !                                                                   
    2001     callstats_omp = .false.                                             
    2002     call getin('callstats', callstats_omp)                                 
     1994    callstats_omp = .FALSE.                                             
     1995    CALL getin('callstats', callstats_omp)                                 
    20031996    !
    20041997    !Config Key  = ecrit_LES
     
    20102003    !
    20112004    ecrit_LES_omp = 1./8.
    2012     call getin('ecrit_LES', ecrit_LES_omp)
     2005    CALL getin('ecrit_LES', ecrit_LES_omp)
    20132006    !
    20142007    read_climoz = 0 ! default value
    2015     call getin('read_climoz', read_climoz)
     2008    CALL getin('read_climoz', read_climoz)
    20162009
    20172010    carbon_cycle_tr_omp=.FALSE.
     
    21242117    t_coupl = t_coupl_omp
    21252118
    2126     ok_veget=.true.
     2119    ok_veget=.TRUE.
    21272120    type_veget=type_veget_omp
    2128     if (type_veget=='n' .or. type_veget=='bucket' .or. type_veget=='betaclim') &
    2129          then
    2130        ok_veget=.false.
    2131     endif
     2121    IF (type_veget=='n' .or. type_veget=='bucket' .or. type_veget=='betaclim') THEN
     2122       ok_veget=.FALSE.
     2123    ENDIF
    21322124    ! Martin
    21332125    ok_snow = ok_snow_omp
     
    22262218    iflag_z0_oce=iflag_z0_oce_omp
    22272219
    2228 
    22292220    z0m_seaice=z0m_seaice_omp
    22302221    z0h_seaice=z0h_seaice_omp
     
    22702261       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid in coupled configuration'
    22712262       CALL abort_physic('conf_phys','version_ocean not valid',1)
    2272     END IF
     2263    ENDIF
    22732264
    22742265    IF (type_ocean=='slab' .AND. version_ocean=='xxxxxx') THEN
     
    22782269       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean'
    22792270       CALL abort_physic('conf_phys','version_ocean not valid',1)
    2280     END IF
     2271    ENDIF
    22812272
    22822273    !--test on radiative scheme
     
    23002291       CALL abort_physic('conf_phys','iflag_rrtm not valid for StratAer',1)
    23012292    ENDIF
     2293    IF (NSW .NE. 6) THEN
     2294       WRITE(lunout,*) ' ERROR NSW<>6 but StratAer activated'
     2295       CALL abort_physic('conf_phys','NSW not valid for StratAer',1)
     2296    ENDIF
    23022297#endif
    23032298
     
    23132308       IF ( flag_aerosol .EQ. 0 ) THEN
    23142309          CALL abort_physic('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
    2315        END IF
     2310       ENDIF
    23162311       IF ( .NOT. new_aod .AND.  flag_aerosol .NE. 1) THEN
    23172312          CALL abort_physic('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
    2318        END IF
    2319     END IF
     2313       ENDIF
     2314    ENDIF
    23202315
    23212316    ! Flag_aerosol cannot be to zero if we are in coupled mode for aerosol
     
    25392534    !$OMP END MASTER
    25402535
    2541     return
    2542 
    2543   end subroutine conf_phys
    2544 
    2545 end module conf_phys_m
     2536    RETURN
     2537
     2538  END SUBROUTINE conf_phys
     2539
     2540END MODULE conf_phys_m
    25462541!
    25472542!#################################################################
    25482543!
    25492544
    2550 subroutine conf_interface(tau_calv)
    2551 
    2552   use IOIPSL
     2545SUBROUTINE conf_interface(tau_calv)
     2546
     2547  USE IOIPSL
    25532548  USE print_control_mod, ONLY: lunout
    2554   implicit none
     2549  IMPLICIT NONE
    25552550  ! Configuration de l'interace atm/surf
    25562551  !
     
    25682563  tau_calv_omp = 360.*10.
    25692564  !$OMP MASTER
    2570   call getin('tau_calv',tau_calv_omp)
     2565  CALL getin('tau_calv',tau_calv_omp)
    25712566  !$OMP END MASTER
    25722567  !$OMP BARRIER
     
    25802575  !$OMP END MASTER
    25812576
    2582   return
    2583 
    2584 end subroutine conf_interface
     2577  RETURN
     2578
     2579END SUBROUTINE conf_interface
Note: See TracChangeset for help on using the changeset viewer.