Changeset 4535


Ignore:
Timestamp:
May 13, 2023, 2:12:05 PM (12 months ago)
Author:
evignon
Message:

poursuite de la replay-isation de lscp en vue de la session
de reecriture de lscp_mod en juin

Location:
LMDZ6/trunk/libf
Files:
2 deleted
14 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/cloudth_mod.F90

    r4380 r4535  
    11MODULE cloudth_mod
     2
    23
    34  IMPLICIT NONE
     
    1011     &           ratqs,zqs,t)
    1112
     13
     14      use lscp_ini_mod, only: iflag_cloudth_vert
    1215
    1316      IMPLICIT NONE
     
    2427#include "YOETHF.h"
    2528#include "FCTTRE.h"
    26 #include "nuage.h"
    2729
    2830      INTEGER itap,ind1,ind2
     
    262264
    263265      USE ioipsl_getin_p_mod, ONLY : getin_p
     266      use lscp_ini_mod, only: iflag_cloudth_vert
    264267
    265268      IMPLICIT NONE
     
    268271#include "YOETHF.h"
    269272#include "FCTTRE.h"
    270 #include "nuage.h"
    271273     
    272274      INTEGER itap,ind1,ind2
     
    593595     &           ratqs,zqs,t)
    594596
     597      use lscp_ini_mod, only: iflag_cloudth_vert
    595598
    596599      IMPLICIT NONE
     
    607610#include "YOETHF.h"
    608611#include "FCTTRE.h"
    609 #include "nuage.h"
    610612
    611613      INTEGER itap,ind1,ind2
     
    820822!===========================================================================
    821823
    822 
     824      use lscp_ini_mod, only: iflag_cloudth_vert
    823825      USE ioipsl_getin_p_mod, ONLY : getin_p
    824826      USE phys_output_var_mod, ONLY : cloudth_sth,cloudth_senv, &
     
    830832#include "YOETHF.h"
    831833#include "FCTTRE.h"
    832 #include "nuage.h"
    833834     
    834835      INTEGER itap,ind1,ind2
     
    12831284     &           ratqs,zqs,T)
    12841285
    1285 
     1286      use lscp_ini_mod, only: iflag_cloudth_vert
    12861287      USE ioipsl_getin_p_mod, ONLY : getin_p
    12871288      USE phys_output_var_mod, ONLY : cloudth_sth,cloudth_senv, &
     
    12931294#include "YOETHF.h"
    12941295#include "FCTTRE.h"
    1295 #include "nuage.h"
    12961296
    12971297
     
    15501550!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    15511551
    1552 
     1552      use lscp_ini_mod, only: iflag_cloudth_vert
    15531553      USE ioipsl_getin_p_mod, ONLY : getin_p
    15541554      USE phys_output_var_mod, ONLY : cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv
     
    15611561#include "YOETHF.h"
    15621562#include "FCTTRE.h"
    1563 #include "nuage.h"
    15641563     
    15651564
     
    23212320
    23222321    INCLUDE "YOMCST.h"
    2323     INCLUDE "nuage.h"
    23242322
    23252323    INTEGER, INTENT(IN) :: ind1,ind2, klev           ! horizontal and vertical indices and dimensions
  • LMDZ6/trunk/libf/phylmd/conf_phys_m.F90

    r4523 r4535  
    3535
    3636    INCLUDE "conema3.h"
    37     INCLUDE "fisrtilp.h"
    3837    INCLUDE "nuage.h"
    3938    INCLUDE "YOMCST.h"
     
    171170    LOGICAL,SAVE :: ok_adj_ema_omp
    172171    INTEGER,SAVE :: iflag_clw_omp
    173     REAL,SAVE :: cld_lc_lsc_omp,cld_lc_con_omp,cld_tau_lsc_omp,cld_tau_con_omp
    174     REAL,SAVE :: ffallv_lsc_omp, ffallv_con_omp,coef_eva_omp,coef_eva_i_omp
    175     LOGICAL,SAVE :: reevap_ice_omp
    176     INTEGER,SAVE :: iflag_pdf_omp
    177172    INTEGER,SAVE :: iflag_ice_thermo_omp
    178173    LOGICAL,SAVE :: ok_ice_sursat_omp
    179174    LOGICAL,SAVE :: ok_plane_h2o_omp, ok_plane_contrail_omp
    180     INTEGER,SAVE :: iflag_t_glace_omp
    181     INTEGER,SAVE :: iflag_cloudth_vert_omp
    182     INTEGER,SAVE :: iflag_rain_incloud_vol_omp
    183     INTEGER,SAVE :: iflag_vice_omp, iflag_rei_omp
     175    INTEGER,SAVE :: iflag_rei_omp
    184176    REAL,SAVE :: rad_froid_omp, rad_chau1_omp, rad_chau2_omp
    185     REAL,SAVE :: t_glace_min_omp, t_glace_max_omp
    186     REAL,SAVE :: exposant_glace_omp
    187     INTEGER,SAVE :: iflag_gammasat_omp
    188177    REAL,SAVE :: rei_min_omp, rei_max_omp
    189178    INTEGER,SAVE :: iflag_sic_omp, iflag_inertie_omp
     
    234223    INTEGER, SAVE :: iflag_ener_conserv_omp
    235224    LOGICAL, SAVE :: ok_conserv_q_omp
    236     INTEGER, SAVE :: iflag_fisrtilp_qsat_omp
    237     INTEGER, SAVE :: iflag_bergeron_omp
    238225    LOGICAL,SAVE  :: ok_strato_omp
    239226    LOGICAL,SAVE  :: ok_hines_omp, ok_gwd_rando_omp
     
    993980    CALL getin('ok_conserv_q',ok_conserv_q_omp)
    994981
    995     !Config  Key  = iflag_fisrtilp_qsat
    996     !Config  Desc = Flag de fisrtilp
    997     !Config  Def  = 0
    998     !Config  Help = Flag  pour la pluie grande-échelle les options suivantes existent :
    999     !Config         >1 nb iterations pour converger dans le calcul de qsat
    1000     iflag_fisrtilp_qsat_omp = 0
    1001     CALL getin('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat_omp)
    1002 
    1003     !Config  Key  = iflag_bergeron
    1004     !Config  Desc = Flag de fisrtilp
    1005     !Config  Def  = 0
    1006     !Config  Help = Flag  pour la pluie grande-échelle les options suivantes existent :
    1007     !Config         0 pas d effet Bergeron
    1008     !Config         1 effet Bergeron pour T<0
    1009     iflag_bergeron_omp = 0
    1010     CALL getin('iflag_bergeron',iflag_bergeron_omp)
    1011 
    1012982    !
    1013983    !
     
    10681038    iflag_clw_omp = 0
    10691039    CALL getin('iflag_clw',iflag_clw_omp)
    1070     !
    1071     !Config Key  = cld_lc_lsc
    1072     !Config Desc = 
    1073     !Config Def  = 2.6e-4
    1074     !Config Help =
    1075     !
    1076     cld_lc_lsc_omp = 2.6e-4
    1077     CALL getin('cld_lc_lsc',cld_lc_lsc_omp)
    1078     !
    1079     !Config Key  = cld_lc_con
    1080     !Config Desc = 
    1081     !Config Def  = 2.6e-4
    1082     !Config Help =
    1083     !
    1084     cld_lc_con_omp = 2.6e-4
    1085     CALL getin('cld_lc_con',cld_lc_con_omp)
    1086     !
    1087     !Config Key  = cld_tau_lsc
    1088     !Config Desc = 
    1089     !Config Def  = 3600.
    1090     !Config Help =
    1091     !
    1092     cld_tau_lsc_omp = 3600.
    1093     CALL getin('cld_tau_lsc',cld_tau_lsc_omp)
    1094     !
    1095     !Config Key  = cld_tau_con
    1096     !Config Desc = 
    1097     !Config Def  = 3600.
    1098     !Config Help =
    1099     !
    1100     cld_tau_con_omp = 3600.
    1101     CALL getin('cld_tau_con',cld_tau_con_omp)
    1102     !
    1103     !Config Key  = ffallv_lsc
    1104     !Config Desc = 
    1105     !Config Def  = 1.
    1106     !Config Help =
    1107     !
    1108     ffallv_lsc_omp = 1.
    1109     CALL getin('ffallv_lsc',ffallv_lsc_omp)
    1110     !
    1111     !Config Key  = ffallv_con
    1112     !Config Desc = 
    1113     !Config Def  = 1.
    1114     !Config Help =
    1115     !
    1116     ffallv_con_omp = 1.
    1117     CALL getin('ffallv_con',ffallv_con_omp)
    1118     !
    1119     !Config Key  = coef_eva
    1120     !Config Desc = 
    1121     !Config Def  = 2.e-5
    1122     !Config Help =
    1123     !
    1124     coef_eva_omp = 2.e-5
    1125     CALL getin('coef_eva',coef_eva_omp)
    1126     !
    1127     !Config Key  = coef_eva_i
    1128     !Config Desc = 
    1129     !Config Def  = 2.e-5
    1130     !Config Help =
    1131     !
    1132     coef_eva_i_omp = coef_eva_omp
    1133     CALL getin('coef_eva_i',coef_eva_i_omp)
    1134     !
    1135     !Config Key  = reevap_ice
    1136     !Config Desc = 
    1137     !Config Def  = .FALSE.
    1138     !Config Help =
    1139     !
    1140     reevap_ice_omp = .FALSE.
    1141     CALL getin('reevap_ice',reevap_ice_omp)
     1040   
    11421041
    11431042    !Config Key  = iflag_ratqs
     
    12551154
    12561155    !
    1257     !Config Key  = iflag_pdf
    1258     !Config Desc = 
    1259     !Config Def  = 0
    1260     !Config Help =
    1261     !
    1262     iflag_pdf_omp = 0
    1263     CALL getin('iflag_pdf',iflag_pdf_omp)
    1264     !
    12651156    !Config Key  = fact_cldcon
    12661157    !Config Desc = 
     
    14131304    CALL getin('rad_chau2',rad_chau2_omp)
    14141305
    1415     !
    1416     !Config Key  = t_glace_min
    1417     !Config Desc = 
    1418     !Config Def  = 258.
    1419     !Config Help =
    1420     !
    1421     t_glace_min_omp = 258.
    1422     CALL getin('t_glace_min',t_glace_min_omp)
    1423 
    1424     !
    1425     !Config Key  = t_glace_max
    1426     !Config Desc = 
    1427     !Config Def  = 273.13
    1428     !Config Help =
    1429     !
    1430     t_glace_max_omp = 273.13
    1431     CALL getin('t_glace_max',t_glace_max_omp)
    1432 
    1433     !
    1434     !Config Key  = exposant_glace
    1435     !Config Desc = 
    1436     !Config Def  = 2.
    1437     !Config Help =
    1438     !
    1439     exposant_glace_omp = 1.
    1440     CALL getin('exposant_glace',exposant_glace_omp)
    1441 
    1442     !
    1443     !Config Key  = iflag_gammasat
    1444     !Config Desc = 
    1445     !Config Def  = 0
    1446     !Config Help =
    1447     !
    1448     iflag_gammasat_omp=0
    1449     CALL getin('iflag_gammasat',iflag_gammasat_omp)
    1450 
    1451 
    1452     !
    1453     !Config Key  = iflag_t_glace
    1454     !Config Desc = 
    1455     !Config Def  = 0
    1456     !Config Help =
    1457     !
    1458     iflag_t_glace_omp = 0
    1459     CALL getin('iflag_t_glace',iflag_t_glace_omp)
    1460 
    1461     !
    1462     !Config Key  = iflag_cloudth_vert
    1463     !Config Desc = 
    1464     !Config Def  = 0
    1465     !Config Help =
    1466     !
    1467     iflag_cloudth_vert_omp = 0
    1468     CALL getin('iflag_cloudth_vert',iflag_cloudth_vert_omp)
    1469 
    1470     !
    1471     !Config Key  = iflag_rain_incloud_vol
    1472     !Config Desc = 
    1473     !Config Def  = 0
    1474     !Config Help =
    1475     !
    1476     iflag_rain_incloud_vol_omp = 0
    1477     CALL getin('iflag_rain_incloud_vol',iflag_rain_incloud_vol_omp)
    1478 
    1479     !
    1480     !Config Key  = iflag_vice
    1481     !Config Desc = 
    1482     !Config Def  = 0
    1483     !Config Help =
    1484     !
    1485     iflag_vice_omp = 0
    1486     CALL getin('iflag_vice',iflag_vice_omp)
    14871306
    14881307    !Config Key  = iflag_rei
     
    24652284    iflag_ener_conserv = iflag_ener_conserv_omp
    24662285    ok_conserv_q = ok_conserv_q_omp
    2467     iflag_fisrtilp_qsat = iflag_fisrtilp_qsat_omp
    2468     iflag_bergeron = iflag_bergeron_omp
    2469 
    24702286    epmax = epmax_omp
    24712287    coef_epmax_cape = coef_epmax_cape_omp
    24722288    ok_adj_ema = ok_adj_ema_omp
    24732289    iflag_clw = iflag_clw_omp
    2474     cld_lc_lsc = cld_lc_lsc_omp
    2475     cld_lc_con = cld_lc_con_omp
    2476     cld_tau_lsc = cld_tau_lsc_omp
    2477     cld_tau_con = cld_tau_con_omp
    2478     ffallv_lsc = ffallv_lsc_omp
    2479     ffallv_con = ffallv_con_omp
    2480     coef_eva = coef_eva_omp
    2481     coef_eva_i = coef_eva_i_omp
    2482     reevap_ice = reevap_ice_omp
    2483     iflag_pdf = iflag_pdf_omp
    24842290    solarlong0 = solarlong0_omp
    24852291    qsol0 = qsol0_omp
     
    24972303    rad_chau1 = rad_chau1_omp
    24982304    rad_chau2 = rad_chau2_omp
    2499     t_glace_min = t_glace_min_omp
    2500     t_glace_max = t_glace_max_omp
    2501     exposant_glace = exposant_glace_omp
    2502     iflag_gammasat=iflag_gammasat_omp
    2503     iflag_t_glace = iflag_t_glace_omp
    2504     iflag_cloudth_vert=iflag_cloudth_vert_omp
    2505     iflag_rain_incloud_vol=iflag_rain_incloud_vol_omp
    2506     iflag_vice=iflag_vice_omp
    25072305    iflag_rei=iflag_rei_omp
    25082306    iflag_ice_thermo = iflag_ice_thermo_omp
     
    28932691    WRITE(lunout,*) ' iflag_ener_conserv=',iflag_ener_conserv
    28942692    WRITE(lunout,*) ' ok_conserv_q=',ok_conserv_q
    2895     WRITE(lunout,*) ' iflag_fisrtilp_qsat=',iflag_fisrtilp_qsat
    2896     WRITE(lunout,*) ' iflag_bergeron=',iflag_bergeron
    28972693    WRITE(lunout,*) ' epmax = ', epmax
    28982694    WRITE(lunout,*) ' coef_epmax_cape = ', coef_epmax_cape
    28992695    WRITE(lunout,*) ' ok_adj_ema = ', ok_adj_ema
    29002696    WRITE(lunout,*) ' iflag_clw = ', iflag_clw
    2901     WRITE(lunout,*) ' cld_lc_lsc = ', cld_lc_lsc
    2902     WRITE(lunout,*) ' cld_lc_con = ', cld_lc_con
    2903     WRITE(lunout,*) ' cld_tau_lsc = ', cld_tau_lsc
    2904     WRITE(lunout,*) ' cld_tau_con = ', cld_tau_con
    2905     WRITE(lunout,*) ' ffallv_lsc = ', ffallv_lsc
    2906     WRITE(lunout,*) ' ffallv_con = ', ffallv_con
    2907     WRITE(lunout,*) ' coef_eva = ', coef_eva
    2908     WRITE(lunout,*) ' coef_eva_i = ', coef_eva_i
    2909     WRITE(lunout,*) ' reevap_ice = ', reevap_ice
    2910     WRITE(lunout,*) ' iflag_pdf = ', iflag_pdf
    29112697    WRITE(lunout,*) ' iflag_cld_th = ', iflag_cld_th
    29122698    WRITE(lunout,*) ' iflag_cld_cv = ', iflag_cld_cv
     
    29302716    WRITE(lunout,*) ' rad_chau1 = ',rad_chau1
    29312717    WRITE(lunout,*) ' rad_chau2 = ',rad_chau2
    2932     WRITE(lunout,*) ' t_glace_min = ',t_glace_min
    2933     WRITE(lunout,*) ' t_glace_max = ',t_glace_max
    2934     WRITE(lunout,*) ' exposant_glace = ',exposant_glace
    2935     WRITE(lunout,*) ' iflag_gammasat = ',iflag_gammasat
    2936     WRITE(lunout,*) ' iflag_t_glace = ',iflag_t_glace
    2937     WRITE(lunout,*) ' iflag_cloudth_vert = ',iflag_cloudth_vert
    2938     WRITE(lunout,*) ' iflag_rain_incloud_vol = ',iflag_rain_incloud_vol
    2939     WRITE(lunout,*) ' iflag_vice = ',iflag_vice
    29402718    WRITE(lunout,*) ' iflag_rei = ',iflag_rei
    29412719    WRITE(lunout,*) ' iflag_ice_thermo = ',iflag_ice_thermo
  • LMDZ6/trunk/libf/phylmd/fisrtilp.F90

    r4380 r4535  
    2020  ! flag to include modifications to ensure energy conservation (if flag >0)
    2121  USE add_phys_tend_mod, only : fl_cor_ebil
     22  USE lscp_ini_mod, ONLY: iflag_t_glace,t_glace_min, t_glace_max, exposant_glace
     23  USE lscp_ini_mod, ONLY: iflag_cloudth_vert, iflag_rain_incloud_vol
     24  USE lscp_ini_mod, ONLY: coef_eva, coef_eva_i, ffallv_lsc, ffallv_con
     25  USE lscp_ini_mod, ONLY: cld_tau_lsc, cld_tau_con, cld_lc_lsc, cld_lc_con
     26  USE lscp_ini_mod, ONLY: reevap_ice, iflag_bergeron, iflag_fisrtilp_qsat, iflag_pdf
     27
     28
    2229  IMPLICIT none
    2330  !======================================================================
     
    4754  !======================================================================
    4855  include "YOMCST.h"
    49   include "fisrtilp.h"
    50   include "nuage.h" ! JBM (3/14)
    51 
    5256  !
    5357  ! Principaux inputs:
     
    228232                     ! (Heymsfield & Donner, 1990)
    229233  REAL zzz
    230 
    231234  include "YOETHF.h"
    232235  include "FCTTRE.h"
  • LMDZ6/trunk/libf/phylmd/ice_sursat_mod.F90

    r4260 r4535  
    308308  INCLUDE "YOETHF.h"
    309309  INCLUDE "FCTTRE.h"
    310   INCLUDE "fisrtilp.h"
    311310  INCLUDE "clesphys.h"
    312311
  • LMDZ6/trunk/libf/phylmd/icefrac_lsc_mod.F90

    r3102 r4535  
    1717 
    1818  USE print_control_mod, ONLY: lunout, prt_level
    19   INCLUDE "nuage.h"
    20 
    21   ! nuage.h contains:
     19  USE lscp_ini_mod, ONLY: t_glace_min, t_glace_max, exposant_glace, iflag_t_glace
     20  ! lscp_ini contains:
    2221  ! t_glace_min: if T < Tmin, the cloud is only made of water ice
    2322  ! t_glace_max: if T > Tmax, the cloud is only made of liquid water
  • LMDZ6/trunk/libf/phylmd/lscp_ini_mod.F90

    r4420 r4535  
    55  ! PARAMETERS for lscp:
    66  !--------------------
    7  
     7 
     8  REAL RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG
     9  !$OMP THREADPRIVATE(RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG)
     10
    811  REAL, SAVE :: seuil_neb=0.001                 ! cloud fraction threshold: a cloud really exists when exceeded
    912  !$OMP THREADPRIVATE(seuil_neb)
     
    4144  !$OMP THREADPRIVATE(ok_debug_autoconversion)
    4245
     46  REAL, SAVE :: t_glace_min=258.0                ! lower-bound temperature parameter for cloud phase determination
     47  !$OMP THREADPRIVATE(t_glace_min)
     48
     49  REAL, SAVE :: t_glace_max=273.15               ! upper-bound temperature parameter for cloud phase determination
     50  !$OMP THREADPRIVATE(t_glace_max)
     51
     52  REAL, SAVE :: exposant_glace=1.0               ! parameter for cloud phase determination
     53  !$OMP THREADPRIVATE(exposant_glace)
     54
     55  INTEGER, SAVE :: iflag_vice=0                  ! which expression for ice crystall fall velocity
     56  !$OMP THREADPRIVATE(iflag_vice)
     57
     58  INTEGER, SAVE :: iflag_t_glace=0               ! which expression for cloud phase partitioning
     59  !$OMP THREADPRIVATE(iflag_t_glace)
     60
     61  INTEGER, SAVE :: iflag_cloudth_vert=0          ! option for determining cloud fraction and content in convective boundary layers
     62  !$OMP THREADPRIVATE(iflag_cloudth_vert)
     63
     64  INTEGER, SAVE :: iflag_gammasat=0              ! which threshold for homogeneous nucleation below -40oC
     65  !$OMP THREADPRIVATE(iflag_gammasat)
     66
     67  INTEGER, SAVE :: iflag_rain_incloud_vol=0      ! use of volume cloud fraction for rain autoconversion
     68  !$OMP THREADPRIVATE(iflag_rain_incloud_vol)
     69
     70  INTEGER, SAVE :: iflag_bergeron=0              ! bergeron effect for liquid precipitation treatment 
     71  !$OMP THREADPRIVATE(iflag_bergeron)
     72
     73  INTEGER, SAVE :: iflag_fisrtilp_qsat=0         ! qsat adjustment (iterative) during autoconversion
     74  !$OMP THREADPRIVATE(iflag_fisrtilp_qsat)
     75
     76  INTEGER, SAVE :: iflag_pdf=0                   ! type of subgrid scale qtot pdf
     77  !$OMP THREADPRIVATE(iflag_pdf)
     78
     79  LOGICAL, SAVE :: reevap_ice=.false.            ! no liquid precip for T< threshold
     80  !$OMP THREADPRIVATE(reevap_ice)
     81
     82  REAL, SAVE :: cld_lc_lsc=2.6e-4                ! liquid autoconversion coefficient, stratiform rain
     83  !$OMP THREADPRIVATE(cld_lc_lsc)
     84
     85  REAL, SAVE :: cld_lc_con=2.6e-4                ! liquid autoconversion coefficient, convective rain
     86  !$OMP THREADPRIVATE(cld_lc_con)
     87
     88  REAL, SAVE :: cld_tau_lsc=3600.                ! liquid autoconversion timescale, stratiform rain
     89  !$OMP THREADPRIVATE(cld_tau_lsc)
     90
     91  REAL, SAVE :: cld_tau_con=3600.                ! liquid autoconversion timescale, convective rain
     92  !$OMP THREADPRIVATE(cld_tau_con)
     93
     94  REAL, SAVE :: ffallv_lsc=1.                    ! tuning coefficient crystal fall velocity, stratiform
     95  !$OMP THREADPRIVATE(ffallv_lsc)
     96
     97  REAL, SAVE :: ffallv_con=1.                    ! tuning coefficient crystal fall velocity, convective
     98  !$OMP THREADPRIVATE(ffallv_con)
     99
     100  REAL, SAVE :: coef_eva=2e-5                    ! tuning coefficient liquid precip evaporation
     101  !$OMP THREADPRIVATE(coef_eva)
     102
     103  REAL, SAVE :: coef_eva_i                       ! tuning coefficient ice precip sublimation
     104  !$OMP THREADPRIVATE(coef_eva_i)
     105
     106
     107
    43108
    44109CONTAINS
    45110
    46 SUBROUTINE lscp_ini(dtime,ok_ice_sursat)
     111SUBROUTINE lscp_ini(dtime,ok_ice_sursat, RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, &
     112                    RVTMP2_in, RTT_in,RD_in,RG_in)
    47113
    48114
     
    53119   REAL, INTENT(IN)      :: dtime
    54120   LOGICAL, INTENT(IN)   :: ok_ice_sursat 
     121
     122   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
     123   REAL, INTENT(IN)      ::  RVTMP2_in, RTT_in, RD_in, RG_in
     124
     125
     126    RG=RG_in
     127    RD=RD_in
     128    RCPD=RCPD_in
     129    RLVTT=RLVTT_in
     130    RLSTT=RLSTT_in
     131    RLMLT=RLMLT_in
     132    RTT=RTT_in
     133    RG=RG_in
     134    RVTMP2=RVTMP2_in
     135
     136
    55137
    56138    CALL getin_p('ninter',ninter)
     
    61143    CALL getin_p('ok_radocond_snow',ok_radocond_snow)
    62144    CALL getin_p('ok_debug_autoconversion',ok_debug_autoconversion)   
     145    CALL getin_p('t_glace_max',t_glace_max)
     146    CALL getin_p('t_glace_min',t_glace_min)
     147    CALL getin_p('exposant_glace',exposant_glace)
     148    CALL getin_p('iflag_vice',iflag_vice)
     149    CALL getin_p('iflag_t_glace',iflag_t_glace)
     150    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
     151    CALL getin_p('iflag_gammasat',iflag_gammasat)
     152    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
     153    CALL getin_p('iflag_bergeron',iflag_bergeron)
     154    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
     155    CALL getin_p('iflag_pdf',iflag_pdf)
     156    CALL getin_p('reevap_ice',reevap_ice)
     157    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
     158    CALL getin_p('cld_lc_con',cld_lc_con)
     159    CALL getin_p('cld_tau_lsc',cld_tau_lsc)
     160    CALL getin_p('cld_tau_con',cld_tau_con)
     161    CALL getin_p('ffallv_lsc',ffallv_lsc)
     162    CALL getin_p('ffallv_lsc',ffallv_con)
     163    CALL getin_p('coef_eva',coef_eva)
     164    coef_eva_i=coef_eva
     165    CALL getin_p('coef_eva_i',coef_eva_i)
     166
     167
     168
     169
    63170    WRITE(lunout,*) 'lscp, ninter:', ninter
    64171    WRITE(lunout,*) 'lscp, iflag_evap_prec:', iflag_evap_prec
     
    68175    WRITE(lunout,*) 'lscp, ok_radocond_snow:', ok_radocond_snow
    69176    WRITE(lunout,*) 'lscp, ok_debug_autoconversion:', ok_debug_autoconversion
     177    WRITE(lunout,*) 'lscp, t_glace_max:', t_glace_max
     178    WRITE(lunout,*) 'lscp, t_glace_min:', t_glace_min
     179    WRITE(lunout,*) 'lscp, exposant_glace:', exposant_glace
     180    WRITE(lunout,*) 'lscp, iflag_vice:', iflag_vice
     181    WRITE(lunout,*) 'lscp, iflag_t_glace:', iflag_t_glace
     182    WRITE(lunout,*) 'lscp, iflag_cloudth_vert:', iflag_cloudth_vert
     183    WRITE(lunout,*) 'lscp, iflag_gammasat:', iflag_gammasat
     184    WRITE(lunout,*) 'lscp, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
     185    WRITE(lunout,*) 'lscp, iflag_bergeron:', iflag_bergeron
     186    WRITE(lunout,*) 'lscp, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
     187    WRITE(lunout,*) 'lscp, iflag_pdf', iflag_pdf
     188    WRITE(lunout,*) 'lscp, reevap_ice', reevap_ice
     189    WRITE(lunout,*) 'lscp, cld_lc_lsc', cld_lc_lsc
     190    WRITE(lunout,*) 'lscp, cld_lc_con', cld_lc_con
     191    WRITE(lunout,*) 'lscp, cld_tau_lsc', cld_tau_lsc
     192    WRITE(lunout,*) 'lscp, cld_tau_con', cld_tau_con
     193    WRITE(lunout,*) 'lscp, ffallv_lsc', ffallv_lsc
     194    WRITE(lunout,*) 'lscp, ffallv_con', ffallv_con
     195    WRITE(lunout,*) 'lscp, coef_eva', coef_eva
     196    WRITE(lunout,*) 'lscp, coef_eva_i', coef_eva_i
     197
     198
     199
     200
    70201
    71202    ! check for precipitation sub-time steps
  • LMDZ6/trunk/libf/phylmd/lscp_mod.F90

    r4530 r4535  
    9595USE lscp_ini_mod, ONLY : seuil_neb, ninter, iflag_evap_prec, t_coup, DDT0, ztfondue, rain_int_min
    9696USE lscp_ini_mod, ONLY : iflag_mpc_bl, ok_radocond_snow, a_tr_sca, ok_debug_autoconversion
    97 
     97USE lscp_ini_mod, ONLY : iflag_cloudth_vert, iflag_rain_incloud_vol, iflag_t_glace, t_glace_min
     98USE lscp_ini_mod, ONLY : coef_eva, coef_eva_i,cld_tau_lsc, cld_tau_con, cld_lc_lsc, cld_lc_con
     99USE lscp_ini_mod, ONLY : iflag_bergeron, iflag_fisrtilp_qsat
     100USE lscp_ini_mod, ONLY : RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG
    98101
    99102IMPLICIT NONE
     
    102105! VARIABLES DECLARATION
    103106!===============================================================================
    104 
    105 include "YOMCST.h"
    106 include "YOETHF.h"
    107 include "fisrtilp.h"
    108 include "nuage.h"
    109107
    110108! INPUT VARIABLES:
     
    726724                  ! saturation may occur at a humidity different from qsat (gamma qsat), so gamma correction for dqs
    727725                  zdqs(:) = gammasat(:)*zdqs(:)+zqs(:)*dgammasatdt(:)
    728                   CALL icefrac_lscp(klon, zt(:),pplay(:,k)/paprs(:,1),zfice(:),dzfice(:))
     726                  CALL icefrac_lscp(klon, zt(:), iflag_ice_thermo, pplay(:,k)/paprs(:,1),zfice(:),dzfice(:))
    729727
    730728                  DO i=1,klon !todoan : check if loop in i is needed
     
    821819
    822820        ! Partition function in stratiform clouds (will be overwritten in boundary-layer MPCs)
    823         CALL icefrac_lscp(klon,zt(:),pplay(:,k)/paprs(:,1),zfice(:), dzfice(:))
     821        CALL icefrac_lscp(klon,zt(:),iflag_ice_thermo,pplay(:,k)/paprs(:,1),zfice(:), dzfice(:))
    824822
    825823        DO i=1, klon
  • LMDZ6/trunk/libf/phylmd/lscp_tools_mod.F90

    r4072 r4535  
    1616    ! 3212–3234. https://doi.org/10.1029/2019MS001642
    1717   
    18    
    19     IMPLICIT NONE
    20 
    21     INCLUDE "nuage.h"
    22     INCLUDE "fisrtilp.h"
     18    use lscp_ini_mod, only: iflag_vice, ffallv_con, ffallv_lsc
     19
     20    IMPLICIT NONE
    2321
    2422    INTEGER, INTENT(IN) :: klon
     
    109107
    110108!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    111 SUBROUTINE ICEFRAC_LSCP(klon, temp, sig, icefrac, dicefracdT)
     109SUBROUTINE ICEFRAC_LSCP(klon, temp, iflag_ice_thermo, sig, icefrac, dicefracdT)
    112110!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    113111 
     
    120118
    121119    USE print_control_mod, ONLY: lunout, prt_level
    122 
    123     IMPLICIT NONE
    124 
    125 
    126     INCLUDE "YOMCST.h"
    127     INCLUDE "nuage.h"
    128     INCLUDE "clesphys.h"
    129 
    130 
    131   ! nuage.h contains:
    132   ! t_glace_min: if T < Tmin, the cloud is only made of water ice
    133   ! t_glace_max: if T > Tmax, the cloud is only made of liquid water
    134   ! exposant_glace: controls the sharpness of the transition
     120    USE lscp_ini_mod, ONLY: t_glace_min, t_glace_max, exposant_glace, iflag_t_glace
     121    USE lscp_ini_mod, ONLY : RTT
     122
     123    IMPLICIT NONE
     124
    135125
    136126    INTEGER, INTENT(IN)                 :: klon       ! number of horizontal grid points
    137127    REAL, INTENT(IN), DIMENSION(klon)   :: temp       ! temperature
    138128    REAL, INTENT(IN), DIMENSION(klon)   :: sig
     129    INTEGER, INTENT(IN)                 :: iflag_ice_thermo
    139130    REAL, INTENT(OUT), DIMENSION(klon)  :: icefrac
    140131    REAL, INTENT(OUT), DIMENSION(klon)  :: dicefracdT
     
    276267!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    277268
    278 
    279     IMPLICIT NONE
    280 
    281     include "YOMCST.h"
    282     include "YOETHF.h"
    283     include "FCTTRE.h"
    284     include "nuage.h"
     269    use lscp_ini_mod, only: iflag_gammasat, t_glace_min, RTT
     270
     271    IMPLICIT NONE
     272
    285273
    286274    INTEGER, INTENT(IN) :: klon                       ! number of horizontal grid points
  • LMDZ6/trunk/libf/phylmd/newmicro.F90

    r4119 r4535  
    1212  USE phys_state_var_mod, ONLY: rnebcon, clwcon
    1313  USE icefrac_lsc_mod ! computes ice fraction (JBM 3/14)
     14  USE lscp_ini_mod, only: iflag_t_glace
    1415  USE ioipsl_getin_p_mod, ONLY : getin_p
    1516  USE print_control_mod, ONLY: lunout
     
    241242
    242243      IF (ok_new_lscp) THEN
    243           CALL icefrac_lscp(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:,k),dzfice(:,k))
     244          CALL icefrac_lscp(klon,t(:,k),iflag_ice_thermo,pplay(:,k)/paprs(:,1),zfice(:,k),dzfice(:,k))
    244245      ELSE
    245246          CALL icefrac_lsc(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:,k))
  • LMDZ6/trunk/libf/phylmd/nuage.F90

    r3999 r4535  
    77  USE lscp_tools_mod, only: icefrac_lscp
    88  USE icefrac_lsc_mod ! computes ice fraction (JBM 3/14)
     9  USE lscp_ini_mod, only : iflag_t_glace
    910  USE phys_local_var_mod, ONLY: ptconv
    1011  IMPLICIT NONE
     
    112113!                           t_glace_max, exposant_glace)
    113114        IF (ok_new_lscp) THEN
    114             CALL icefrac_lscp(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:),dzfice(:))
     115            CALL icefrac_lscp(klon,t(:,k),iflag_ice_thermo,pplay(:,k)/paprs(:,1),zfice(:),dzfice(:))
    115116        ELSE
    116117            CALL icefrac_lsc(klon,t(:,k),pplay(:,k)/paprs(:,1),zfice(:))
  • LMDZ6/trunk/libf/phylmd/nuage.h

    r4380 r4535  
    22! $Id$
    33!
    4       REAL rad_froid, rad_chau1, rad_chau2, t_glace_max, t_glace_min
    5       REAL exposant_glace
     4      REAL rad_froid, rad_chau1, rad_chau2
    65      REAL rei_min,rei_max
    76      REAL tau_cld_cv,coefw_cld_cv
    8 
    97      REAL tmax_fonte_cv
    10 
    11       INTEGER iflag_t_glace, iflag_cloudth_vert, iflag_cld_cv
    12       INTEGER iflag_rain_incloud_vol
    13    
    14       INTEGER iflag_gammasat, iflag_vice, iflag_rei
     8      INTEGER iflag_cld_cv
     9      INTEGER iflag_rei
    1510      LOGICAL ok_icefra_lscp
    1611
    17       common /nuagecom/ rad_froid,rad_chau1, rad_chau2,t_glace_max,     &
    18      &                  t_glace_min,exposant_glace,rei_min,rei_max,     &
     12      common /nuagecom/ rad_froid,rad_chau1, rad_chau2,                 &
     13     &                  rei_min,rei_max,                                &
    1914     &                  tau_cld_cv,coefw_cld_cv,                        &
    2015     &                  tmax_fonte_cv,                                  &
    21      &                  iflag_t_glace,iflag_cloudth_vert,iflag_cld_cv,  &
    22      &                  iflag_rain_incloud_vol,                         &
    23      &                  ok_icefra_lscp,                  &
    24      &                  iflag_gammasat, iflag_vice,       &
     16     &                  iflag_cld_cv,                                   &
     17     &                  ok_icefra_lscp,                                 &
    2518     &                  iflag_rei   
    2619!$OMP THREADPRIVATE(/nuagecom/)
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4530 r4535  
    11481148    !IM 100106 BEG : pouvoir sortir les ctes de la physique
    11491149    include "conema3.h"
    1150     include "fisrtilp.h"
    11511150    include "nuage.h"
    11521151    include "compbl.h"
     
    17661765       CALL thermcell_ini(iflag_thermals,prt_level,tau_thermals,lunout, &
    17671766   &    RG,RD,RCPD,RKAPPA,RLVTT,RETV)
    1768        IF (ok_new_lscp) then
    1769            CALL lscp_ini(pdtphys,ok_ice_sursat)
    1770        endif
     1767       CALL lscp_ini(pdtphys,ok_ice_sursat, RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT,RD,RG)
    17711768       CALL blowing_snow_ini(prt_level,lunout, &
    17721769                             RCPD, RLSTT, RLVTT, RLMLT, &
  • LMDZ6/trunk/libf/phylmdiso/fisrtilp.F90

    r4491 r4535  
    2626  ! flag to include modifications to ensure energy conservation (if flag >0)
    2727  USE add_phys_tend_mod, only : fl_cor_ebil
     28  USE lscp_ini_mod, ONLY: iflag_t_glace,t_glace_min, t_glace_max, exposant_glace
     29  USE lscp_ini_mod, ONLY: iflag_cloudth_vert, iflag_rain_incloud_vol
     30  USE lscp_ini_mod, ONLY: coef_eva, coef_eva_i, ffallv_lsc, ffallv_con
     31  USE lscp_ini_mod, ONLY: cld_tau_lsc, cld_tau_con, cld_lc_lsc, cld_lc_con
     32  USE lscp_ini_mod, ONLY: reevap_ice, iflag_bergeron, iflag_fisrtilp_qsat, iflag_pdf
     33
     34
     35
    2836#ifdef ISO
    2937  USE infotrac_phy, ONLY: ntraciso=>ntiso,niso,itZonIso
     
    8290  !======================================================================
    8391  include "YOMCST.h"
    84   include "fisrtilp.h"
    85   include "nuage.h" ! JBM (3/14)
    86 
    8792  !
    8893  ! Principaux inputs:
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r4530 r4535  
    19091909       CALL thermcell_ini(iflag_thermals,prt_level,tau_thermals,lunout, &
    19101910   &    RG,RD,RCPD,RKAPPA,RLVTT,RETV)
    1911        IF (ok_new_lscp) then
    1912            CALL lscp_ini(pdtphys,ok_ice_sursat)
    1913        endif
     1911       CALL lscp_ini(pdtphys,ok_ice_sursat,RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT,RD,RG)
    19141912       CALL blowing_snow_ini(prt_level,lunout, &
    19151913                             RCPD, RLSTT, RLVTT, RLMLT, &
Note: See TracChangeset for help on using the changeset viewer.