Ignore:
Timestamp:
Nov 30, 2016, 1:28:41 PM (8 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2664:2719 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/conf_phys_m.F90

    r2669 r2720  
    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
     209    INTEGER, SAVE :: nbapp_cv_omp
    210210    INTEGER, SAVE :: iflag_ener_conserv_omp
    211211    LOGICAL, SAVE :: ok_conserv_q_omp
    212212    INTEGER, SAVE :: iflag_fisrtilp_qsat_omp
    213213    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
     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
    225225    ! Allowed values are 0, 1 and 2
    226226    ! 0: do not read an ozone climatology
     
    239239    !
    240240    type_ocean_omp = 'force '
    241     call getin('type_ocean', type_ocean_omp)
     241    CALL getin('type_ocean', type_ocean_omp)
    242242    !
    243243    !Config Key  = version_ocean
     
    247247    !
    248248    version_ocean_omp = 'xxxxxx'
    249     call getin('version_ocean', version_ocean_omp)
     249    CALL getin('version_ocean', version_ocean_omp)
    250250
    251251    !Config Key  = OCEAN
     
    255255    !
    256256    ocean_omp = 'yyyyyy'
    257     call getin('OCEAN', ocean_omp)
     257    CALL getin('OCEAN', ocean_omp)
    258258    IF (ocean_omp /= 'yyyyyy') THEN
    259259       WRITE(lunout,*)'ERROR! Old variable name OCEAN used in parmeter file.'
     
    261261       WRITE(lunout,*)'You have to update your parameter file physiq.def to succed running'
    262262       CALL abort_physic('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
    263     END IF
     263    ENDIF
    264264
    265265    !Config Key  = t_coupl
     
    269269    !
    270270    t_coupl_omp = 86400.
    271     call getin('t_coupl', t_coupl_omp)
     271    CALL getin('t_coupl', t_coupl_omp)
    272272    IF (t_coupl_omp == 0) THEN
    273273       WRITE(lunout,*)'ERROR! Timestep of coupling between atmosphere and ocean'
    274274       WRITE(lunout,*)'cannot be zero.'
    275275       CALL abort_physic('conf_phys','t_coupl = 0.',1)
    276     END IF
     276    ENDIF
    277277
    278278    !
    279279    !Config Key  = ok_all_xml
    280280    !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)
     281    !Config Def  = .FALSE.
     282    !Config Help =
     283    !
     284    ok_all_xml_omp = .FALSE.
     285    CALL getin('ok_all_xml', ok_all_xml_omp)
    286286    !
    287287
     
    289289    !Config Key  = VEGET
    290290    !Config Desc = Type de modele de vegetation
    291     !Config Def  = .false.
     291    !Config Def  = .FALSE.
    292292    !Config Help = Type de modele de vegetation utilise
    293293    !
    294294    type_veget_omp ='orchidee'
    295     call getin('VEGET', type_veget_omp)
     295    CALL getin('VEGET', type_veget_omp)
    296296    !
    297297
     
    299299    !Config Key  = ok_snow
    300300    !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)
     301    !Config Def  = .FALSE.
     302    ok_snow_omp = .FALSE.
     303    CALL getin('ok_snow', ok_snow_omp)
    304304    ! Martin
    305305
    306306    !Config Key  = OK_journe
    307307    !Config Desc = Pour des sorties journalieres
    308     !Config Def  = .false.
     308    !Config Def  = .FALSE.
    309309    !Config Help = Pour creer le fichier histday contenant les sorties
    310310    !              journalieres
    311311    !
    312     ok_journe_omp = .false.
    313     call getin('OK_journe', ok_journe_omp)
     312    ok_journe_omp = .FALSE.
     313    CALL getin('OK_journe', ok_journe_omp)
    314314    !
    315315    !Config Key  = ok_hf
    316316    !Config Desc = Pour des sorties haute frequence
    317     !Config Def  = .false.
     317    !Config Def  = .FALSE.
    318318    !Config Help = Pour creer le fichier histhf contenant les sorties
    319319    !              haute frequence ( 3h ou 6h)
    320320    !
    321     ok_hf_omp = .false.
    322     call getin('ok_hf', ok_hf_omp)
     321    ok_hf_omp = .FALSE.
     322    CALL getin('ok_hf', ok_hf_omp)
    323323    !
    324324    !Config Key  = OK_mensuel
    325325    !Config Desc = Pour des sorties mensuelles
    326     !Config Def  = .true.
     326    !Config Def  = .TRUE.
    327327    !Config Help = Pour creer le fichier histmth contenant les sorties
    328328    !              mensuelles
    329329    !
    330     ok_mensuel_omp = .true.
    331     call getin('OK_mensuel', ok_mensuel_omp)
     330    ok_mensuel_omp = .TRUE.
     331    CALL getin('OK_mensuel', ok_mensuel_omp)
    332332    !
    333333    !Config Key  = OK_instan
    334334    !Config Desc = Pour des sorties instantanees
    335     !Config Def  = .false.
     335    !Config Def  = .FALSE.
    336336    !Config Help = Pour creer le fichier histins contenant les sorties
    337337    !              instantanees
    338338    !
    339     ok_instan_omp = .false.
    340     call getin('OK_instan', ok_instan_omp)
     339    ok_instan_omp = .FALSE.
     340    CALL getin('OK_instan', ok_instan_omp)
    341341    !
    342342    !Config Key  = ok_ade
    343343    !Config Desc = Aerosol direct effect or not?
    344     !Config Def  = .false.
     344    !Config Def  = .FALSE.
    345345    !Config Help = Used in radlwsw.F
    346346    !
    347     ok_ade_omp = .false.
    348     call getin('ok_ade', ok_ade_omp)
     347    ok_ade_omp = .FALSE.
     348    CALL getin('ok_ade', ok_ade_omp)
    349349
    350350    !
    351351    !Config Key  = ok_aie
    352352    !Config Desc = Aerosol indirect effect or not?
    353     !Config Def  = .false.
     353    !Config Def  = .FALSE.
    354354    !Config Help = Used in nuage.F and radlwsw.F
    355355    !
    356     ok_aie_omp = .false.
    357     call getin('ok_aie', ok_aie_omp)
     356    ok_aie_omp = .FALSE.
     357    CALL getin('ok_aie', ok_aie_omp)
    358358
    359359    !
    360360    !Config Key  = ok_cdnc
    361361    !Config Desc = ok cloud droplet number concentration
    362     !Config Def  = .false.
     362    !Config Def  = .FALSE.
    363363    !Config Help = Used in newmicro.F
    364364    !
    365     ok_cdnc_omp = .false.
    366     call getin('ok_cdnc', ok_cdnc_omp)
     365    ok_cdnc_omp = .FALSE.
     366    CALL getin('ok_cdnc', ok_cdnc_omp)
    367367    !
    368368    !Config Key  = aerosol_couple
    369369    !Config Desc = read aerosol in file or calcul by inca
    370     !Config Def  = .false.
     370    !Config Def  = .FALSE.
    371371    !Config Help = Used in physiq.F
    372372    !
    373     aerosol_couple_omp = .false.
     373    aerosol_couple_omp = .FALSE.
    374374    CALL getin('aerosol_couple',aerosol_couple_omp)
    375375    !
     
    410410    !Config Help = Used in physiq.F / aeropt
    411411    !
    412     flag_bc_internal_mixture_omp = .false.
     412    flag_bc_internal_mixture_omp = .FALSE.
    413413    CALL getin('flag_bc_internal_mixture',flag_bc_internal_mixture_omp)
    414414
     
    416416    !Config Key  = new_aod
    417417    !Config Desc = which calcul of aeropt
    418     !Config Def  = false
     418    !Config Def  = FALSE
    419419    !Config Help = Used in physiq.F
    420420    !
    421     new_aod_omp = .true.
     421    new_aod_omp = .TRUE.
    422422    CALL getin('new_aod',new_aod_omp)
    423423
     
    429429    !
    430430    aer_type_omp = 'scenario'
    431     call getin('aer_type', aer_type_omp)
     431    CALL getin('aer_type', aer_type_omp)
    432432
    433433    !
    434434    !Config Key  = bl95_b0
    435435    !Config Desc = Parameter in CDNC-maer link (Boucher&Lohmann 1995)
    436     !Config Def  = .false.
     436    !Config Def  = .FALSE.
    437437    !Config Help = Used in nuage.F
    438438    !
    439439    bl95_b0_omp = 2.
    440     call getin('bl95_b0', bl95_b0_omp)
     440    CALL getin('bl95_b0', bl95_b0_omp)
    441441
    442442    !Config Key  = bl95_b1
    443443    !Config Desc = Parameter in CDNC-maer link (Boucher&Lohmann 1995)
    444     !Config Def  = .false.
     444    !Config Def  = .FALSE.
    445445    !Config Help = Used in nuage.F
    446446    !
    447447    bl95_b1_omp = 0.2
    448     call getin('bl95_b1', bl95_b1_omp)
     448    CALL getin('bl95_b1', bl95_b1_omp)
    449449
    450450    !Config Key  = freq_ISCCP
     
    455455    !
    456456    freq_ISCCP_omp = 10800.
    457     call getin('freq_ISCCP', freq_ISCCP_omp)
     457    CALL getin('freq_ISCCP', freq_ISCCP_omp)
    458458    !
    459459    !Config Key  = ecrit_ISCCP
     
    465465    !
    466466    ecrit_ISCCP_omp = 1.
    467     call getin('ecrit_ISCCP', ecrit_ISCCP_omp)
     467    CALL getin('ecrit_ISCCP', ecrit_ISCCP_omp)
    468468
    469469    !Config Key  = freq_COSP
     
    474474    !
    475475    freq_COSP_omp = 10800.
    476     call getin('freq_COSP', freq_COSP_omp)
     476    CALL getin('freq_COSP', freq_COSP_omp)
    477477
    478478    !Config Key  = freq_AIRS
     
    483483    !
    484484    freq_AIRS_omp = 10800.
    485     call getin('freq_AIRS', freq_AIRS_omp)
     485    CALL getin('freq_AIRS', freq_AIRS_omp)
    486486
    487487    !
     
    492492    !               
    493493    ip_ebil_phy_omp = 0
    494     call getin('ip_ebil_phy', ip_ebil_phy_omp)
     494    CALL getin('ip_ebil_phy', ip_ebil_phy_omp)
     495    IF (ip_ebil_phy_omp/=0) THEN
     496       CALL abort_physic('conf_phys','ip_ebil_phy_omp doit etre 0 sur cette version',1)
     497    ENDIF
     498
    495499    !
    496500    !Config Key  = seuil_inversion
     
    500504    !               
    501505    seuil_inversion_omp = -0.1
    502     call getin('seuil_inversion', seuil_inversion_omp)
     506    CALL getin('seuil_inversion', seuil_inversion_omp)
    503507
    504508    !
     
    512516    !valeur AMIP II
    513517    R_ecc_omp = 0.016715
    514     call getin('R_ecc', R_ecc_omp)
     518    CALL getin('R_ecc', R_ecc_omp)
    515519    !
    516520    !Config Key  = R_peri
     
    522526    !valeur AMIP II
    523527    R_peri_omp = 102.7
    524     call getin('R_peri', R_peri_omp)
     528    CALL getin('R_peri', R_peri_omp)
    525529    !
    526530    !Config Key  = R_incl
     
    532536    !valeur AMIP II
    533537    R_incl_omp = 23.441
    534     call getin('R_incl', R_incl_omp)
     538    CALL getin('R_incl', R_incl_omp)
    535539    !
    536540    !Config Key  = solaire
     
    542546    !valeur AMIP II
    543547    solaire_omp = 1365.
    544     call getin('solaire', solaire_omp)
     548    CALL getin('solaire', solaire_omp)
    545549    !
    546550    !Config Key  = ok_sun_time
    547551    !Config Desc = oui ou non variabilite solaire
    548     !Config Def  = .false.
     552    !Config Def  = .FALSE.
    549553    !Config Help =
    550554    !
    551555    !
    552556    !valeur AMIP II
    553     ok_suntime_rrtm_omp = .false.
    554     call getin('ok_suntime_rrtm',ok_suntime_rrtm_omp)
     557    ok_suntime_rrtm_omp = .FALSE.
     558    CALL getin('ok_suntime_rrtm',ok_suntime_rrtm_omp)
    555559    !
    556560    !Config Key  = co2_ppm
     
    562566    !valeur AMIP II
    563567    co2_ppm_omp = 348.
    564     call getin('co2_ppm', co2_ppm_omp)
     568    CALL getin('co2_ppm', co2_ppm_omp)
    565569    !
    566570    !Config Key  = RCO2
     
    574578    RCO2_omp = co2_ppm_omp * 1.0e-06  * 44.011/28.97 ! pour co2_ppm=348.
    575579
    576     !  call getin('RCO2', RCO2)
     580    !  CALL getin('RCO2', RCO2)
    577581    !
    578582    !Config Key  = RCH4
     
    588592    !ancienne valeur
    589593    ! RCH4 = 1.72E-06* 16.043/28.97
    590     !OK call getin('RCH4', RCH4)
     594    !OK CALL getin('RCH4', RCH4)
    591595    zzz = 1650.
    592     call getin('CH4_ppb', zzz)
     596    CALL getin('CH4_ppb', zzz)
    593597    CH4_ppb_omp = zzz
    594598    RCH4_omp = CH4_ppb_omp * 1.0E-09 * 16.043/28.97
     
    606610    !ancienne valeur
    607611    ! RN2O = 310.E-09* 44.013/28.97
    608     !OK  call getin('RN2O', RN2O)
     612    !OK  CALL getin('RN2O', RN2O)
    609613    zzz=306.
    610     call getin('N2O_ppb', zzz)
     614    CALL getin('N2O_ppb', zzz)
    611615    N2O_ppb_omp = zzz
    612616    RN2O_omp = N2O_ppb_omp * 1.0E-09 * 44.013/28.97
     
    620624    !OK RCFC11 = 280.E-12* 137.3686/28.97
    621625    zzz = 280.
    622     call getin('CFC11_ppt',zzz)
     626    CALL getin('CFC11_ppt',zzz)
    623627    CFC11_ppt_omp = zzz
    624628    RCFC11_omp=CFC11_ppt_omp* 1.0E-12 * 137.3686/28.97
    625629    ! RCFC11 = 1.327690990680013E-09
    626     !OK call getin('RCFC11', RCFC11)
     630    !OK CALL getin('RCFC11', RCFC11)
    627631    !
    628632    !Config Key  = RCFC12
     
    634638    !OK RCFC12 = 484.E-12* 120.9140/28.97
    635639    zzz = 484.
    636     call getin('CFC12_ppt',zzz)
     640    CALL getin('CFC12_ppt',zzz)
    637641    CFC12_ppt_omp = zzz
    638642    RCFC12_omp = CFC12_ppt_omp * 1.0E-12 * 120.9140/28.97
    639643    ! RCFC12 = 2.020102726958923E-09
    640     !OK call getin('RCFC12', RCFC12)
     644    !OK CALL getin('RCFC12', RCFC12)
    641645
    642646    !ajout CFMIP begin
     
    648652    !               
    649653    co2_ppm_per_omp = co2_ppm_omp
    650     call getin('co2_ppm_per', co2_ppm_per_omp)
     654    CALL getin('co2_ppm_per', co2_ppm_per_omp)
    651655    !
    652656    !Config Key  = RCO2_per
     
    660664    !Config Key  = ok_4xCO2atm
    661665    !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)
     666    !Config Def  = .FALSE.
     667    !Config Help =
     668
     669    ok_4xCO2atm_omp = .FALSE.
     670    CALL getin('ok_4xCO2atm',ok_4xCO2atm_omp)
    667671
    668672    !Config Key  = RCH4_per
     
    672676    !               
    673677    zzz = CH4_ppb_omp
    674     call getin('CH4_ppb_per', zzz)
     678    CALL getin('CH4_ppb_per', zzz)
    675679    CH4_ppb_per_omp = zzz
    676680    RCH4_per_omp = CH4_ppb_per_omp * 1.0E-09 * 16.043/28.97
     
    682686    !               
    683687    zzz = N2O_ppb_omp
    684     call getin('N2O_ppb_per', zzz)
     688    CALL getin('N2O_ppb_per', zzz)
    685689    N2O_ppb_per_omp = zzz
    686690    RN2O_per_omp = N2O_ppb_per_omp * 1.0E-09 * 44.013/28.97
     
    692696    !               
    693697    zzz = CFC11_ppt_omp
    694     call getin('CFC11_ppt_per',zzz)
     698    CALL getin('CFC11_ppt_per',zzz)
    695699    CFC11_ppt_per_omp = zzz
    696700    RCFC11_per_omp=CFC11_ppt_per_omp* 1.0E-12 * 137.3686/28.97
     
    702706    !               
    703707    zzz = CFC12_ppt_omp
    704     call getin('CFC12_ppt_per',zzz)
     708    CALL getin('CFC12_ppt_per',zzz)
    705709    CFC12_ppt_per_omp = zzz
    706710    RCFC12_per_omp = CFC12_ppt_per_omp * 1.0E-12 * 120.9140/28.97
     
    778782    CALL getin('iflag_con',iflag_con_omp)
    779783
     784    !Config  Key  = nbapp_cv
     785    !Config  Desc = Frequence d'appel a la convection
     786    !Config  Def  = 0
     787    !Config  Help = Nombre  d'appels des routines de convection
     788    !Config         par jour. Si =0, appel a chaque pas de temps physique.
     789    nbapp_cv_omp = 0
     790    CALL getin('nbapp_cv',nbapp_cv_omp)
     791
    780792    !Config  Key  = iflag_ener_conserv
    781793    !Config  Desc = Flag de convection
     
    851863    !
    852864    epmax_omp = .993
    853     call getin('epmax', epmax_omp)
     865    CALL getin('epmax', epmax_omp)
    854866
    855867    coef_epmax_cape_omp = 0.0   
    856     call getin('coef_epmax_cape', coef_epmax_cape_omp)       
     868    CALL getin('coef_epmax_cape', coef_epmax_cape_omp)       
    857869    !
    858870    !Config Key  = ok_adj_ema
    859871    !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)
     872    !Config Def  = FALSE
     873    !Config Help =
     874    !
     875    ok_adj_ema_omp = .FALSE.
     876    CALL getin('ok_adj_ema',ok_adj_ema_omp)
    865877    !
    866878    !Config Key  = iflag_clw
     
    870882    !
    871883    iflag_clw_omp = 0
    872     call getin('iflag_clw',iflag_clw_omp)
     884    CALL getin('iflag_clw',iflag_clw_omp)
    873885    !
    874886    !Config Key  = cld_lc_lsc
     
    878890    !
    879891    cld_lc_lsc_omp = 2.6e-4
    880     call getin('cld_lc_lsc',cld_lc_lsc_omp)
     892    CALL getin('cld_lc_lsc',cld_lc_lsc_omp)
    881893    !
    882894    !Config Key  = cld_lc_con
     
    886898    !
    887899    cld_lc_con_omp = 2.6e-4
    888     call getin('cld_lc_con',cld_lc_con_omp)
     900    CALL getin('cld_lc_con',cld_lc_con_omp)
    889901    !
    890902    !Config Key  = cld_tau_lsc
     
    894906    !
    895907    cld_tau_lsc_omp = 3600.
    896     call getin('cld_tau_lsc',cld_tau_lsc_omp)
     908    CALL getin('cld_tau_lsc',cld_tau_lsc_omp)
    897909    !
    898910    !Config Key  = cld_tau_con
     
    902914    !
    903915    cld_tau_con_omp = 3600.
    904     call getin('cld_tau_con',cld_tau_con_omp)
     916    CALL getin('cld_tau_con',cld_tau_con_omp)
    905917    !
    906918    !Config Key  = ffallv_lsc
     
    910922    !
    911923    ffallv_lsc_omp = 1.
    912     call getin('ffallv_lsc',ffallv_lsc_omp)
     924    CALL getin('ffallv_lsc',ffallv_lsc_omp)
    913925    !
    914926    !Config Key  = ffallv_con
     
    918930    !
    919931    ffallv_con_omp = 1.
    920     call getin('ffallv_con',ffallv_con_omp)
     932    CALL getin('ffallv_con',ffallv_con_omp)
    921933    !
    922934    !Config Key  = coef_eva
     
    926938    !
    927939    coef_eva_omp = 2.e-5
    928     call getin('coef_eva',coef_eva_omp)
     940    CALL getin('coef_eva',coef_eva_omp)
    929941    !
    930942    !Config Key  = reevap_ice
    931943    !Config Desc = 
    932     !Config Def  = .false.
    933     !Config Help =
    934     !
    935     reevap_ice_omp = .false.
    936     call getin('reevap_ice',reevap_ice_omp)
     944    !Config Def  = .FALSE.
     945    !Config Help =
     946    !
     947    reevap_ice_omp = .FALSE.
     948    CALL getin('reevap_ice',reevap_ice_omp)
    937949
    938950    !Config Key  = iflag_ratqs
     
    942954    !
    943955    iflag_ratqs_omp = 1
    944     call getin('iflag_ratqs',iflag_ratqs_omp)
     956    CALL getin('iflag_ratqs',iflag_ratqs_omp)
    945957
    946958    !
     
    951963    !
    952964    iflag_radia_omp = 1
    953     call getin('iflag_radia',iflag_radia_omp)
     965    CALL getin('iflag_radia',iflag_radia_omp)
    954966
    955967    !
     
    960972    !
    961973    iflag_rrtm_omp = 0
    962     call getin('iflag_rrtm',iflag_rrtm_omp)
     974    CALL getin('iflag_rrtm',iflag_rrtm_omp)
    963975
    964976    !
     
    969981    !
    970982    NSW_omp = 2
    971     call getin('NSW',NSW_omp)
     983    CALL getin('NSW',NSW_omp)
    972984    !albedo SB >>>
    973985    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)
     986    CALL getin('iflag_albedo',iflag_albedo_omp)
     987
     988    ok_chlorophyll_omp=.FALSE.
     989    CALL getin('ok_chlorophyll',ok_chlorophyll_omp)
    978990    !albedo SB <<<
    979991
     
    9881000    ! pour assurer une retrocompatiblite.
    9891001    ! A abandonner un jour
    990     call getin('iflag_cldcon',iflag_cld_th_omp)
    991     call getin('iflag_cld_th',iflag_cld_th_omp)
     1002    CALL getin('iflag_cldcon',iflag_cld_th_omp)
     1003    CALL getin('iflag_cld_th',iflag_cld_th_omp)
    9921004    iflag_cld_cv_omp = 0
    993     call getin('iflag_cld_cv',iflag_cld_cv_omp)
     1005    CALL getin('iflag_cld_cv',iflag_cld_cv_omp)
    9941006
    9951007    !
     
    10001012    !
    10011013    tau_cld_cv_omp = 10.
    1002     call getin('tau_cld_cv',tau_cld_cv_omp)
     1014    CALL getin('tau_cld_cv',tau_cld_cv_omp)
    10031015
    10041016    !
     
    10091021    !
    10101022    coefw_cld_cv_omp = 0.1
    1011     call getin('coefw_cld_cv',coefw_cld_cv_omp)
     1023    CALL getin('coefw_cld_cv',coefw_cld_cv_omp)
    10121024
    10131025
     
    10211033    !
    10221034    iflag_pdf_omp = 0
    1023     call getin('iflag_pdf',iflag_pdf_omp)
     1035    CALL getin('iflag_pdf',iflag_pdf_omp)
    10241036    !
    10251037    !Config Key  = fact_cldcon
     
    10291041    !
    10301042    fact_cldcon_omp = 0.375
    1031     call getin('fact_cldcon',fact_cldcon_omp)
     1043    CALL getin('fact_cldcon',fact_cldcon_omp)
    10321044
    10331045    !
     
    10381050    !
    10391051    facttemps_omp = 1.e-4
    1040     call getin('facttemps',facttemps_omp)
     1052    CALL getin('facttemps',facttemps_omp)
    10411053
    10421054    !
    10431055    !Config Key  = ok_newmicro
    10441056    !Config Desc = 
    1045     !Config Def  = .true.
    1046     !Config Help =
    1047     !
    1048     ok_newmicro_omp = .true.
    1049     call getin('ok_newmicro',ok_newmicro_omp)
     1057    !Config Def  = .TRUE.
     1058    !Config Help =
     1059    !
     1060    ok_newmicro_omp = .TRUE.
     1061    CALL getin('ok_newmicro',ok_newmicro_omp)
    10501062    !
    10511063    !Config Key  = ratqsbas
     
    10551067    !
    10561068    ratqsbas_omp = 0.01
    1057     call getin('ratqsbas',ratqsbas_omp)
     1069    CALL getin('ratqsbas',ratqsbas_omp)
    10581070    !
    10591071    !Config Key  = ratqshaut
     
    10631075    !
    10641076    ratqshaut_omp = 0.3
    1065     call getin('ratqshaut',ratqshaut_omp)
     1077    CALL getin('ratqshaut',ratqshaut_omp)
    10661078
    10671079    !Config Key  = tau_ratqs
     
    10711083    !
    10721084    tau_ratqs_omp = 1800.
    1073     call getin('tau_ratqs',tau_ratqs_omp)
     1085    CALL getin('tau_ratqs',tau_ratqs_omp)
    10741086
    10751087    !
     
    10831095    !
    10841096    solarlong0_omp = -999.999
    1085     call getin('solarlong0',solarlong0_omp)
     1097    CALL getin('solarlong0',solarlong0_omp)
    10861098    !
    10871099    !-----------------------------------------------------------------------
     
    10901102    ! Default value -1 to activate the full computation
    10911103    qsol0_omp = -1.
    1092     call getin('qsol0',qsol0_omp)
     1104    CALL getin('qsol0',qsol0_omp)
    10931105    evap0_omp = -1.
    1094     call getin('evap0',evap0_omp)
     1106    CALL getin('evap0',evap0_omp)
    10951107    albsno0_omp = -1.
    1096     call getin('albsno0',albsno0_omp)
     1108    CALL getin('albsno0',albsno0_omp)
    10971109    !
    10981110    !-----------------------------------------------------------------------
     
    11041116    !
    11051117    inertie_ice_omp = 2000.
    1106     call getin('inertie_ice',inertie_ice_omp)
     1118    CALL getin('inertie_ice',inertie_ice_omp)
    11071119    !
    11081120    !Config Key  = inertie_sno
     
    11121124    !
    11131125    inertie_sno_omp = 2000.
    1114     call getin('inertie_sno',inertie_sno_omp)
     1126    CALL getin('inertie_sno',inertie_sno_omp)
    11151127    !
    11161128    !Config Key  = inertie_sol
     
    11201132    !
    11211133    inertie_sol_omp = 2000.
    1122     call getin('inertie_sol',inertie_sol_omp)
     1134    CALL getin('inertie_sol',inertie_sol_omp)
    11231135
    11241136    !
     
    11291141    !
    11301142    rad_froid_omp = 35.0
    1131     call getin('rad_froid',rad_froid_omp)
     1143    CALL getin('rad_froid',rad_froid_omp)
    11321144
    11331145    !
     
    11381150    !
    11391151    rad_chau1_omp = 13.0
    1140     call getin('rad_chau1',rad_chau1_omp)
     1152    CALL getin('rad_chau1',rad_chau1_omp)
    11411153
    11421154    !
     
    11471159    !
    11481160    rad_chau2_omp = 9.0
    1149     call getin('rad_chau2',rad_chau2_omp)
     1161    CALL getin('rad_chau2',rad_chau2_omp)
    11501162
    11511163    !
     
    11561168    !
    11571169    t_glace_min_omp = 258.
    1158     call getin('t_glace_min',t_glace_min_omp)
     1170    CALL getin('t_glace_min',t_glace_min_omp)
    11591171
    11601172    !
     
    11651177    !
    11661178    t_glace_max_omp = 273.13
    1167     call getin('t_glace_max',t_glace_max_omp)
     1179    CALL getin('t_glace_max',t_glace_max_omp)
    11681180
    11691181    !
     
    11741186    !
    11751187    exposant_glace_omp = 1.
    1176     call getin('exposant_glace',exposant_glace_omp)
     1188    CALL getin('exposant_glace',exposant_glace_omp)
    11771189
    11781190    !
     
    11831195    !
    11841196    iflag_t_glace_omp = 0
    1185     call getin('iflag_t_glace',iflag_t_glace_omp)
     1197    CALL getin('iflag_t_glace',iflag_t_glace_omp)
    11861198
    11871199    !
     
    11921204    !
    11931205    iflag_cloudth_vert_omp = 0
    1194     call getin('iflag_cloudth_vert',iflag_cloudth_vert_omp)
     1206    CALL getin('iflag_cloudth_vert',iflag_cloudth_vert_omp)
    11951207
    11961208    !
     
    12011213    !
    12021214    iflag_ice_thermo_omp = 0
    1203     call getin('iflag_ice_thermo',iflag_ice_thermo_omp)
     1215    CALL getin('iflag_ice_thermo',iflag_ice_thermo_omp)
    12041216
    12051217    !Config Key  = rei_min
     
    12091221    !
    12101222    rei_min_omp = 3.5
    1211     call getin('rei_min',rei_min_omp)
     1223    CALL getin('rei_min',rei_min_omp)
    12121224
    12131225    !
     
    12181230    !
    12191231    rei_max_omp = 61.29
    1220     call getin('rei_max',rei_max_omp)
     1232    CALL getin('rei_max',rei_max_omp)
    12211233
    12221234    !
     
    12271239    !
    12281240    top_height_omp = 3
    1229     call getin('top_height',top_height_omp)
     1241    CALL getin('top_height',top_height_omp)
    12301242
    12311243    !
     
    12361248    !
    12371249    overlap_omp = 3
    1238     call getin('overlap',overlap_omp)
    1239 
    1240 
    1241     !
     1250    CALL getin('overlap',overlap_omp)
     1251
    12421252    !
    12431253    !Config Key  = cdmmax
     
    12471257    !
    12481258    cdmmax_omp = 1.3E-3
    1249     call getin('cdmmax',cdmmax_omp)
     1259    CALL getin('cdmmax',cdmmax_omp)
    12501260
    12511261    !
     
    12561266    !
    12571267    cdhmax_omp = 1.1E-3
    1258     call getin('cdhmax',cdhmax_omp)
     1268    CALL getin('cdhmax',cdhmax_omp)
    12591269
    12601270    !261103
     
    12661276    !
    12671277    ksta_omp = 1.0e-10
    1268     call getin('ksta',ksta_omp)
     1278    CALL getin('ksta',ksta_omp)
    12691279
    12701280    !
     
    12751285    !
    12761286    ksta_ter_omp = 1.0e-10
    1277     call getin('ksta_ter',ksta_ter_omp)
     1287    CALL getin('ksta_ter',ksta_ter_omp)
    12781288
    12791289    !Config Key  = f_ri_cd_min
     
    12831293    !
    12841294    f_ri_cd_min_omp = 0.1
    1285     call getin('f_ri_cd_min',f_ri_cd_min_omp)
     1295    CALL getin('f_ri_cd_min',f_ri_cd_min_omp)
    12861296
    12871297    !
    12881298    !Config Key  = ok_kzmin
    12891299    !Config Desc =
    1290     !Config Def  = .true.
    1291     !Config Help =
    1292     !
    1293     ok_kzmin_omp = .true.
    1294     call getin('ok_kzmin',ok_kzmin_omp)
     1300    !Config Def  = .TRUE.
     1301    !Config Help =
     1302    !
     1303    ok_kzmin_omp = .TRUE.
     1304    CALL getin('ok_kzmin',ok_kzmin_omp)
    12951305
    12961306    pbl_lmixmin_alpha_omp=0.0
    1297     call getin('pbl_lmixmin_alpha',pbl_lmixmin_alpha_omp)
    1298 
     1307    CALL getin('pbl_lmixmin_alpha',pbl_lmixmin_alpha_omp)
    12991308
    13001309    !
     
    13051314    !
    13061315    fmagic_omp = 1.
    1307     call getin('fmagic',fmagic_omp)
     1316    CALL getin('fmagic',fmagic_omp)
    13081317
    13091318    !
     
    13141323    !
    13151324    pmagic_omp = 0.
    1316     call getin('pmagic',pmagic_omp)
     1325    CALL getin('pmagic',pmagic_omp)
    13171326
    13181327
    13191328    !Config Key = ok_lic_melt
    13201329    !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)
     1330    !Config Def  = .FALSE.
     1331    !Config Help = mettre a .FALSE. pour assurer la conservation en eau
     1332    ok_lic_melt_omp = .FALSE.
     1333    CALL getin('ok_lic_melt', ok_lic_melt_omp)
    13251334
    13261335    !
     
    13341343    !
    13351344    iflag_pbl_omp = 1
    1336     call getin('iflag_pbl',iflag_pbl_omp)
     1345    CALL getin('iflag_pbl',iflag_pbl_omp)
    13371346    !
    13381347    !Config Key  = iflag_pbl_split
     
    13421351    !
    13431352    iflag_pbl_split_omp = 0
    1344     call getin('iflag_pbl_split',iflag_pbl_split_omp)
     1353    CALL getin('iflag_pbl_split',iflag_pbl_split_omp)
    13451354    !
    13461355    !Config Key  = iflag_order2_sollw
     
    13501359    !
    13511360    iflag_order2_sollw_omp = 0
    1352     call getin('iflag_order2_sollw',iflag_order2_sollw_omp)
     1361    CALL getin('iflag_order2_sollw',iflag_order2_sollw_omp)
    13531362    !
    13541363    !Config Key  = iflag_thermals
     
    13581367    !
    13591368    iflag_thermals_omp = 0
    1360     call getin('iflag_thermals',iflag_thermals_omp)
     1369    CALL getin('iflag_thermals',iflag_thermals_omp)
    13611370    !
    13621371    !Config Key  = iflag_thermals_ed
     
    13671376    fact_thermals_ed_dz_omp = 0.1
    13681377
    1369     call getin('fact_thermals_ed_dz',fact_thermals_ed_dz_omp)
     1378    CALL getin('fact_thermals_ed_dz',fact_thermals_ed_dz_omp)
    13701379    !
    13711380    !
     
    13761385    !
    13771386    iflag_thermals_ed_omp = 0
    1378     call getin('iflag_thermals_ed',iflag_thermals_ed_omp)
     1387    CALL getin('iflag_thermals_ed',iflag_thermals_ed_omp)
    13791388    !
    13801389    !
     
    13851394    !
    13861395    iflag_thermals_optflux_omp = 0
    1387     call getin('iflag_thermals_optflux',iflag_thermals_optflux_omp)
     1396    CALL getin('iflag_thermals_optflux',iflag_thermals_optflux_omp)
    13881397    !
    13891398    !Config Key  = iflag_thermals_closure
     
    13931402    !
    13941403    iflag_thermals_closure_omp = 1
    1395     call getin('iflag_thermals_closure',iflag_thermals_closure_omp)
    1396     !
    1397     !
    1398     !
     1404    CALL getin('iflag_thermals_closure',iflag_thermals_closure_omp)
    13991405    !
    14001406    !Config Key  = nsplit_thermals
     
    14041410    !
    14051411    nsplit_thermals_omp = 1
    1406     call getin('nsplit_thermals',nsplit_thermals_omp)
     1412    CALL getin('nsplit_thermals',nsplit_thermals_omp)
    14071413
    14081414    !Config Key  = alp_bl_k
     
    14121418    !
    14131419    alp_bl_k_omp = 1.
    1414     call getin('alp_bl_k',alp_bl_k_omp)
     1420    CALL getin('alp_bl_k',alp_bl_k_omp)
    14151421
    14161422    ! nrlmd le 10/04/2012
     
    14221428    !
    14231429    iflag_trig_bl_omp = 0
    1424     call getin('iflag_trig_bl',iflag_trig_bl_omp)
     1430    CALL getin('iflag_trig_bl',iflag_trig_bl_omp)
    14251431
    14261432    !Config Key  = s_trig_bl
     
    14301436    !
    14311437    s_trig_omp = 2e7
    1432     call getin('s_trig',s_trig_omp)
     1438    CALL getin('s_trig',s_trig_omp)
    14331439
    14341440    !Config Key  = tau_trig_shallow
     
    14381444    !
    14391445    tau_trig_shallow_omp = 600
    1440     call getin('tau_trig_shallow',tau_trig_shallow_omp)
     1446    CALL getin('tau_trig_shallow',tau_trig_shallow_omp)
    14411447
    14421448    !Config Key  = tau_trig_deep
     
    14461452    !
    14471453    tau_trig_deep_omp = 1800
    1448     call getin('tau_trig_deep',tau_trig_deep_omp)
     1454    CALL getin('tau_trig_deep',tau_trig_deep_omp)
    14491455
    14501456    !Config Key  = iflag_clos_bl
     
    14541460    !
    14551461    iflag_clos_bl_omp = 0
    1456     call getin('iflag_clos_bl',iflag_clos_bl_omp)
     1462    CALL getin('iflag_clos_bl',iflag_clos_bl_omp)
    14571463
    14581464    ! fin nrlmd le 10/04/2012
     
    14651471    !
    14661472    tau_thermals_omp = 0.
    1467     call getin('tau_thermals',tau_thermals_omp)
     1473    CALL getin('tau_thermals',tau_thermals_omp)
    14681474
    14691475    !
     
    14741480    !
    14751481    iflag_coupl_omp = 0
    1476     call getin('iflag_coupl',iflag_coupl_omp)
     1482    CALL getin('iflag_coupl',iflag_coupl_omp)
    14771483
    14781484    !
     
    14831489    !
    14841490    iflag_clos_omp = 1
    1485     call getin('iflag_clos',iflag_clos_omp)
     1491    CALL getin('iflag_clos',iflag_clos_omp)
    14861492    !
    14871493    !Config Key  = coef_clos_ls
     
    14911497    !
    14921498    coef_clos_ls_omp = 0.
    1493     call getin('coef_clos_ls',coef_clos_ls_omp)
     1499    CALL getin('coef_clos_ls',coef_clos_ls_omp)
    14941500
    14951501    !
     
    15001506    !
    15011507    iflag_cvl_sigd_omp = 0
    1502     call getin('iflag_cvl_sigd',iflag_cvl_sigd_omp)
     1508    CALL getin('iflag_cvl_sigd',iflag_cvl_sigd_omp)
    15031509
    15041510    !Config Key  = iflag_wake
     
    15081514    !
    15091515    iflag_wake_omp = 0
    1510     call getin('iflag_wake',iflag_wake_omp)
     1516    CALL getin('iflag_wake',iflag_wake_omp)
    15111517
    15121518    !Config Key  = alp_offset
     
    15161522    !
    15171523    alp_offset_omp = 0.
    1518     call getin('alp_offset',alp_offset_omp)
     1524    CALL getin('alp_offset',alp_offset_omp)
    15191525
    15201526    !
     
    15251531    !
    15261532    lev_histhf_omp = 1
    1527     call getin('lev_histhf',lev_histhf_omp)
     1533    CALL getin('lev_histhf',lev_histhf_omp)
    15281534
    15291535    !
     
    15341540    !
    15351541    lev_histday_omp = 1
    1536     call getin('lev_histday',lev_histday_omp)
     1542    CALL getin('lev_histday',lev_histday_omp)
    15371543
    15381544    !
     
    15431549    !
    15441550    lev_histmth_omp = 2
    1545     call getin('lev_histmth',lev_histmth_omp)
     1551    CALL getin('lev_histmth',lev_histmth_omp)
    15461552    !
    15471553    !Config Key  = lev_histins
     
    15511557    !
    15521558    lev_histins_omp = 1
    1553     call getin('lev_histins',lev_histins_omp)
     1559    CALL getin('lev_histins',lev_histins_omp)
    15541560    !
    15551561    !Config Key  = lev_histLES
     
    15591565    !
    15601566    lev_histLES_omp = 1
    1561     call getin('lev_histLES',lev_histLES_omp)
     1567    CALL getin('lev_histLES',lev_histLES_omp)
    15621568    !
    15631569    !Config Key  = lev_histdayNMC
     
    15671573    !
    15681574    lev_histdayNMC_omp = 8
    1569     call getin('lev_histdayNMC',lev_histdayNMC_omp)
     1575    CALL getin('lev_histdayNMC',lev_histdayNMC_omp)
    15701576    !
    15711577    !Config Key  = levout_histNMC
     
    15771583    levout_histNMC_omp(2) = 5
    15781584    levout_histNMC_omp(3) = 5
    1579     call getin('levout_histNMC',levout_histNMC_omp)
     1585    CALL getin('levout_histNMC',levout_histNMC_omp)
    15801586    !
    15811587    !histNMC BEG
     
    15871593    !Config Help =
    15881594    !
    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)
     1595    ok_histNMC_omp(1) = .FALSE.
     1596    ok_histNMC_omp(2) = .FALSE.
     1597    ok_histNMC_omp(3) = .FALSE.
     1598    CALL getin('ok_histNMC',ok_histNMC_omp)
    15931599    !
    15941600    !Config Key  = freq_outNMC
     
    16021608    freq_outNMC_omp(2) = 1.
    16031609    freq_outNMC_omp(3) = 1./4.
    1604     call getin('freq_outNMC',freq_outNMC_omp)
     1610    CALL getin('freq_outNMC',freq_outNMC_omp)
    16051611    !
    16061612    !Config Key  = freq_calNMC
     
    16141620    freq_calNMC_omp(2) = pasphys
    16151621    freq_calNMC_omp(3) = pasphys
    1616     call getin('freq_calNMC',freq_calNMC_omp)
     1622    CALL getin('freq_calNMC',freq_calNMC_omp)
    16171623    !
    16181624    !Config Key  = type_run
     
    16221628    !
    16231629    type_run_omp = 'AMIP'
    1624     call getin('type_run',type_run_omp)
     1630    CALL getin('type_run',type_run_omp)
    16251631
    16261632    !
    16271633    !Config Key  = ok_cosp
    16281634    !Config Desc =
    1629     !Config Def  = .false.
    1630     !Config Help =
    1631     !
    1632     ok_cosp_omp = .false.
    1633     call getin('ok_cosp',ok_cosp_omp)
     1635    !Config Def  = .FALSE.
     1636    !Config Help =
     1637    !
     1638    ok_cosp_omp = .FALSE.
     1639    CALL getin('ok_cosp',ok_cosp_omp)
    16341640
    16351641    !
    16361642    !Config Key  = ok_airs
    16371643    !Config Desc =
    1638     !Config Def  = .false.
    1639     !Config Help =
    1640     !
    1641     ok_airs_omp = .false.
    1642     call getin('ok_airs',ok_airs_omp)
     1644    !Config Def  = .FALSE.
     1645    !Config Help =
     1646    !
     1647    ok_airs_omp = .FALSE.
     1648    CALL getin('ok_airs',ok_airs_omp)
    16431649
    16441650    !
    16451651    !Config Key  = ok_mensuelCOSP
    16461652    !Config Desc =
    1647     !Config Def  = .true.
    1648     !Config Help =
    1649     !
    1650     ok_mensuelCOSP_omp = .true.
    1651     call getin('ok_mensuelCOSP',ok_mensuelCOSP_omp)
     1653    !Config Def  = .TRUE.
     1654    !Config Help =
     1655    !
     1656    ok_mensuelCOSP_omp = .TRUE.
     1657    CALL getin('ok_mensuelCOSP',ok_mensuelCOSP_omp)
    16521658
    16531659    !
    16541660    !Config Key  = ok_journeCOSP
    16551661    !Config Desc =
    1656     !Config Def  = .true.
    1657     !Config Help =
    1658     !
    1659     ok_journeCOSP_omp = .true.
    1660     call getin('ok_journeCOSP',ok_journeCOSP_omp)
     1662    !Config Def  = .TRUE.
     1663    !Config Help =
     1664    !
     1665    ok_journeCOSP_omp = .TRUE.
     1666    CALL getin('ok_journeCOSP',ok_journeCOSP_omp)
    16611667
    16621668    !
    16631669    !Config Key  = ok_hfCOSP
    16641670    !Config Desc =
    1665     !Config Def  = .false.
    1666     !Config Help =
    1667     !
    1668     ok_hfCOSP_omp = .false.
    1669     call getin('ok_hfCOSP',ok_hfCOSP_omp)
     1671    !Config Def  = .FALSE.
     1672    !Config Help =
     1673    !
     1674    ok_hfCOSP_omp = .FALSE.
     1675    CALL getin('ok_hfCOSP',ok_hfCOSP_omp)
    16701676
    16711677    !
     
    16791685    !
    16801686    lonmin_ins_omp = 100.
    1681     call getin('lonmin_ins',lonmin_ins_omp)
     1687    CALL getin('lonmin_ins',lonmin_ins_omp)
    16821688    !
    16831689    !Config Key  = lonmax_ins
     
    16871693    !
    16881694    lonmax_ins_omp = 130.
    1689     call getin('lonmax_ins',lonmax_ins_omp)
     1695    CALL getin('lonmax_ins',lonmax_ins_omp)
    16901696    !
    16911697    !Config Key  = latmin_ins
     
    16951701    !
    16961702    latmin_ins_omp = -20.
    1697     call getin('latmin_ins',latmin_ins_omp)
     1703    CALL getin('latmin_ins',latmin_ins_omp)
    16981704    !
    16991705    !Config Key  = latmax_ins
     
    17031709    !
    17041710    latmax_ins_omp = 20.
    1705     call getin('latmax_ins',latmax_ins_omp)
     1711    CALL getin('latmax_ins',latmax_ins_omp)
    17061712    !
    17071713    !Config Key  = ecrit_hf
     
    17111717    !
    17121718    ecrit_hf_omp = 1./8.
    1713     call getin('ecrit_hf',ecrit_hf_omp)
     1719    CALL getin('ecrit_hf',ecrit_hf_omp)
    17141720    !
    17151721    !Config Key  = ecrit_ins
     
    17191725    !
    17201726    ecrit_ins_omp = 1./48.
    1721     call getin('ecrit_ins',ecrit_ins_omp)
     1727    CALL getin('ecrit_ins',ecrit_ins_omp)
    17221728    !
    17231729    !Config Key  = ecrit_day
     
    17271733    !
    17281734    ecrit_day_omp = 1.0
    1729     call getin('ecrit_day',ecrit_day_omp)
     1735    CALL getin('ecrit_day',ecrit_day_omp)
    17301736    !
    17311737    !Config Key  = ecrit_mth
     
    17351741    !
    17361742    ecrit_mth_omp = 30.
    1737     call getin('ecrit_mth',ecrit_mth_omp)
     1743    CALL getin('ecrit_mth',ecrit_mth_omp)
    17381744    !
    17391745    !Config Key  = ecrit_tra
     
    17431749    !
    17441750    ecrit_tra_omp = 0.
    1745     call getin('ecrit_tra',ecrit_tra_omp)
     1751    CALL getin('ecrit_tra',ecrit_tra_omp)
    17461752    !
    17471753    !Config Key  = ecrit_reg
     
    17511757    !
    17521758    ecrit_reg_omp = 0.25   !4 fois par jour
    1753     call getin('ecrit_reg',ecrit_reg_omp)
     1759    CALL getin('ecrit_reg',ecrit_reg_omp)
    17541760    !
    17551761    !
     
    17591765    !
    17601766    f_cdrag_ter_omp = 0.8
    1761     call getin('f_cdrag_ter',f_cdrag_ter_omp)
     1767    CALL getin('f_cdrag_ter',f_cdrag_ter_omp)
    17621768    !
    17631769    f_cdrag_oce_omp = 0.8
    1764     call getin('f_cdrag_oce',f_cdrag_oce_omp)
     1770    CALL getin('f_cdrag_oce',f_cdrag_oce_omp)
    17651771    !
    17661772
    17671773    ! Gustiness flags
    17681774    f_z0qh_oce_omp = 1.
    1769     call getin('f_z0qh_oce',f_z0qh_oce_omp)
     1775    CALL getin('f_z0qh_oce',f_z0qh_oce_omp)
    17701776    !
    17711777    f_qsat_oce_omp = 1.
    1772     call getin('f_qsat_oce',f_qsat_oce_omp)
     1778    CALL getin('f_qsat_oce',f_qsat_oce_omp)
    17731779    !
    17741780    f_gust_bl_omp = 0.
    1775     call getin('f_gust_bl',f_gust_bl_omp)
     1781    CALL getin('f_gust_bl',f_gust_bl_omp)
    17761782    !
    17771783    f_gust_wk_omp = 0.
    1778     call getin('f_gust_wk',f_gust_wk_omp)
     1784    CALL getin('f_gust_wk',f_gust_wk_omp)
    17791785    !
    17801786    !Config Key  = iflag_z0_oce
     
    17841790    !
    17851791    iflag_z0_oce_omp=0
    1786     call getin('iflag_z0_oce',iflag_z0_oce_omp)
     1792    CALL getin('iflag_z0_oce',iflag_z0_oce_omp)
    17871793    !
    17881794    iflag_gusts_omp=0
    1789     call getin('iflag_gusts',iflag_gusts_omp)
     1795    CALL getin('iflag_gusts',iflag_gusts_omp)
    17901796    !
    17911797    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)
     1798    CALL getin('min_wind_speed',min_wind_speed_omp)
     1799
     1800    z0m_seaice_omp = 0.002 ; CALL getin('z0m_seaice',z0m_seaice_omp)
     1801    z0h_seaice_omp = 0.002 ; CALL getin('z0h_seaice',z0h_seaice_omp)
    17961802
    17971803    f_rugoro_omp = 0.
    1798     call getin('f_rugoro',f_rugoro_omp)
     1804    CALL getin('f_rugoro',f_rugoro_omp)
    17991805
    18001806    z0min_omp = 0.000015
    1801     call getin('z0min',z0min_omp)
     1807    CALL getin('z0min',z0min_omp)
    18021808
    18031809
     
    18101816    !
    18111817    supcrit1_omp = .540
    1812     call getin('supcrit1',supcrit1_omp)
     1818    CALL getin('supcrit1',supcrit1_omp)
    18131819
    18141820    !
     
    18191825    !
    18201826    supcrit2_omp = .600
    1821     call getin('supcrit2',supcrit2_omp)
     1827    CALL getin('supcrit2',supcrit2_omp)
    18221828
    18231829    !
     
    18341840    !
    18351841    iflag_mix_omp = 1
    1836     call getin('iflag_mix',iflag_mix_omp)
     1842    CALL getin('iflag_mix',iflag_mix_omp)
    18371843
    18381844!
     
    18481854    !
    18491855    iflag_mix_adiab_omp = 0
    1850     call getin('iflag_mix_adiab',iflag_mix_adiab_omp)
     1856    CALL getin('iflag_mix_adiab',iflag_mix_adiab_omp)
    18511857
    18521858    !
     
    18571863    !
    18581864    scut_omp = 0.95
    1859     call getin('scut',scut_omp)
     1865    CALL getin('scut',scut_omp)
    18601866
    18611867    !
     
    18661872    !
    18671873    qqa1_omp = 1.0
    1868     call getin('qqa1',qqa1_omp)
     1874    CALL getin('qqa1',qqa1_omp)
    18691875
    18701876    !
     
    18751881    !
    18761882    qqa2_omp = 0.0
    1877     call getin('qqa2',qqa2_omp)
     1883    CALL getin('qqa2',qqa2_omp)
    18781884
    18791885    !
     
    18841890    !
    18851891    gammas_omp = 0.05
    1886     call getin('gammas',gammas_omp)
     1892    CALL getin('gammas',gammas_omp)
    18871893
    18881894    !
     
    18931899    !
    18941900    Fmax_omp = 0.65
    1895     call getin('Fmax',Fmax_omp)
     1901    CALL getin('Fmax',Fmax_omp)
    18961902
    18971903    !
     
    19021908    !
    19031909    tmax_fonte_cv_omp = 275.15
    1904     call getin('tmax_fonte_cv',tmax_fonte_cv_omp)
     1910    CALL getin('tmax_fonte_cv',tmax_fonte_cv_omp)
    19051911
    19061912    !
     
    19111917    !
    19121918    alphas_omp = -5.
    1913     call getin('alphas',alphas_omp)
     1919    CALL getin('alphas',alphas_omp)
    19141920
    19151921    !Config key = ok_strato
     
    19861992    !Config Key  = OK_LES                                               
    19871993    !Config Desc = Pour des sorties LES                                 
    1988     !Config Def  = .false.                                             
     1994    !Config Def  = .FALSE.                                             
    19891995    !Config Help = Pour creer le fichier histLES contenant les sorties 
    19901996    !              LES                                                 
    19911997    !                                                                   
    1992     ok_LES_omp = .false.                                             
    1993     call getin('OK_LES', ok_LES_omp)                                 
     1998    ok_LES_omp = .FALSE.                                             
     1999    CALL getin('OK_LES', ok_LES_omp)                                 
    19942000
    19952001    !Config Key  = callstats                                               
    19962002    !Config Desc = Pour des sorties callstats                                 
    1997     !Config Def  = .false.                                             
     2003    !Config Def  = .FALSE.                                             
    19982004    !Config Help = Pour creer le fichier stats contenant les sorties 
    19992005    !              stats                                                 
    20002006    !                                                                   
    2001     callstats_omp = .false.                                             
    2002     call getin('callstats', callstats_omp)                                 
     2007    callstats_omp = .FALSE.                                             
     2008    CALL getin('callstats', callstats_omp)                                 
    20032009    !
    20042010    !Config Key  = ecrit_LES
     
    20102016    !
    20112017    ecrit_LES_omp = 1./8.
    2012     call getin('ecrit_LES', ecrit_LES_omp)
     2018    CALL getin('ecrit_LES', ecrit_LES_omp)
    20132019    !
    20142020    read_climoz = 0 ! default value
    2015     call getin('read_climoz', read_climoz)
     2021    CALL getin('read_climoz', read_climoz)
    20162022
    20172023    carbon_cycle_tr_omp=.FALSE.
     
    20592065    nbapp_rad = nbapp_rad_omp
    20602066    iflag_con = iflag_con_omp
     2067    nbapp_cv = nbapp_cv_omp
    20612068    iflag_ener_conserv = iflag_ener_conserv_omp
    20622069    ok_conserv_q = ok_conserv_q_omp
     
    21242131    t_coupl = t_coupl_omp
    21252132
    2126     ok_veget=.true.
     2133    ok_veget=.TRUE.
    21272134    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
     2135    IF (type_veget=='n' .or. type_veget=='bucket' .or. type_veget=='betaclim') THEN
     2136       ok_veget=.FALSE.
     2137    ENDIF
    21322138    ! Martin
    21332139    ok_snow = ok_snow_omp
     
    22262232    iflag_z0_oce=iflag_z0_oce_omp
    22272233
    2228 
    22292234    z0m_seaice=z0m_seaice_omp
    22302235    z0h_seaice=z0h_seaice_omp
     
    22702275       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid in coupled configuration'
    22712276       CALL abort_physic('conf_phys','version_ocean not valid',1)
    2272     END IF
     2277    ENDIF
    22732278
    22742279    IF (type_ocean=='slab' .AND. version_ocean=='xxxxxx') THEN
     
    22782283       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean'
    22792284       CALL abort_physic('conf_phys','version_ocean not valid',1)
    2280     END IF
     2285    ENDIF
    22812286
    22822287    !--test on radiative scheme
     
    22952300       CALL abort_physic('conf_phys','choice iflag_rrtm not valid',1)
    22962301    ENDIF
     2302#ifdef CPP_StratAer
     2303    IF (iflag_rrtm .NE. 1) THEN
     2304       WRITE(lunout,*) ' ERROR iflag_rrtm<>1 but StratAer activated'
     2305       CALL abort_physic('conf_phys','iflag_rrtm not valid for StratAer',1)
     2306    ENDIF
     2307    IF (NSW .NE. 6) THEN
     2308       WRITE(lunout,*) ' ERROR NSW<>6 but StratAer activated'
     2309       CALL abort_physic('conf_phys','NSW not valid for StratAer',1)
     2310    ENDIF
     2311#endif
    22972312
    22982313    !--test on ocean surface albedo
     
    23072322       IF ( flag_aerosol .EQ. 0 ) THEN
    23082323          CALL abort_physic('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
    2309        END IF
     2324       ENDIF
    23102325       IF ( .NOT. new_aod .AND.  flag_aerosol .NE. 1) THEN
    23112326          CALL abort_physic('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
    2312        END IF
    2313     END IF
     2327       ENDIF
     2328    ENDIF
    23142329
    23152330    ! Flag_aerosol cannot be to zero if we are in coupled mode for aerosol
     
    23842399    write(lunout,*)'nbapp_rad=',nbapp_rad
    23852400    write(lunout,*)'iflag_con=',iflag_con
     2401    write(lunout,*)'nbapp_cv=',nbapp_cv
    23862402    write(lunout,*)'iflag_ener_conserv=',iflag_ener_conserv
    23872403    write(lunout,*)'ok_conserv_q=',ok_conserv_q
     
    25332549    !$OMP END MASTER
    25342550
    2535     return
    2536 
    2537   end subroutine conf_phys
    2538 
    2539 end module conf_phys_m
     2551    RETURN
     2552
     2553  END SUBROUTINE conf_phys
     2554
     2555END MODULE conf_phys_m
    25402556!
    25412557!#################################################################
    25422558!
    25432559
    2544 subroutine conf_interface(tau_calv)
    2545 
    2546   use IOIPSL
     2560SUBROUTINE conf_interface(tau_calv)
     2561
     2562  USE IOIPSL
    25472563  USE print_control_mod, ONLY: lunout
    2548   implicit none
     2564  IMPLICIT NONE
    25492565  ! Configuration de l'interace atm/surf
    25502566  !
     
    25622578  tau_calv_omp = 360.*10.
    25632579  !$OMP MASTER
    2564   call getin('tau_calv',tau_calv_omp)
     2580  CALL getin('tau_calv',tau_calv_omp)
    25652581  !$OMP END MASTER
    25662582  !$OMP BARRIER
     
    25742590  !$OMP END MASTER
    25752591
    2576   return
    2577 
    2578 end subroutine conf_interface
     2592  RETURN
     2593
     2594END SUBROUTINE conf_interface
Note: See TracChangeset for help on using the changeset viewer.