Changeset 5007 for LMDZ6


Ignore:
Timestamp:
Jul 4, 2024, 9:29:24 AM (3 months ago)
Author:
evignon
Message:

ajout de la nouvelle paramétrisation du partitonnement de phase
dans les nuages de phase mixte de Lea Raillard
La parametrisation s'active avec iflag_icefrac=1 et est fondé
sur la theorie de creation et maintien de sursaturation en atmosphere
turbulente avec ou sans presence de cristaux de glace

Location:
LMDZ6/trunk
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/DefLists/field_def_lmdz.xml

    r4999 r5007  
    634634        <field id="tke"    long_name="TKE"    unit="m2/s2" />
    635635        <field id="tke_dissip" long_name="TKE DISSIPATION" unit="m2/s3" />
     636        <field id="tke_buoy" long_name="TKE Buoyancy term" unit="m2/s3" />
     637        <field id="tke_shear" long_name="TKE Shear term" unit="m2/s3" />
    636638        <field id="tke_ter"    long_name="Max Turb. Kinetic Energy ter"    unit="m2/s2" />
    637639        <field id="tke_lic"    long_name="Max Turb. Kinetic Energy lic"    unit="m2/s2" />
     
    642644        <field id="tke_max_oce"    long_name="Max Turb. Kinetic Energy oce"    unit="m2/s2" operation="maximum"/>
    643645        <field id="tke_max_sic"    long_name="Max Turb. Kinetic Energy sic"    unit="m2/s2" operation="maximum"/>
    644         <field id="l_mix_ter"    long_name="PBL mixing length ter"    unit="m" />
     646       
     647        <field id="qrain_lsc"    long_name="LS specific rain content"    unit="kg/kg" />
     648        <field id="qsnow_lsc"    long_name="LS specific snow content"    unit="kg/kg" />
     649        <field id="dqreva"    long_name="LS rain tendency due to evaporation"    unit="kg/kg/s" />
     650        <field id="dqssub"    long_name="LS snow tendency due to sublimation"    unit="kg/kg/s" />
     651        <field id="dqrauto"    long_name="LS rain tendency due to autoconversion"    unit="kg/kg/s" />
     652        <field id="dqrcol"    long_name="LS rain tendency due to collection"    unit="kg/kg/s" />
     653        <field id="dqrmelt"    long_name="LS rain tendency due to melting"    unit="kg/kg/s" />
     654        <field id="dqrfreez"    long_name="LS rain tendency due to freezing"    unit="kg/kg/s" />
     655        <field id="dqsauto"    long_name="LS snow tendency due to autoconversion"    unit="kg/kg/s" />
     656        <field id="dqsagg"    long_name="LS snow tendency due to aggregation"    unit="kg/kg/s" />
     657        <field id="dqsrim"    long_name="LS snow tendency due to riming"    unit="kg/kg/s" />
     658        <field id="dqsmelt"    long_name="LS snow tendency due to melting"    unit="kg/kg/s" />
     659        <field id="dqsfreez"    long_name="LS snow tendency due to freezing"    unit="kg/kg/s" />
     660
     661        <field id="l_mix_ter"    long_name="PBL mixing length ter"    unit="m" />
    645662        <field id="l_mix_lic"    long_name="PBL mixing length lic"    unit="m" />
    646663        <field id="l_mix_oce"    long_name="PBL mixing length oce"    unit="m" />
     
    687704        <field id="zfull"    long_name="Altitude of full pressure levels"    unit="m" />
    688705        <field id="zhalf"    long_name="Altitude of half pressure levels"    unit="m" />
    689         <field id="rneb"    long_name="Cloud fraction"    unit="-" />
     706        <field id="rneb"    long_name="Cloud fraction"    unit="-" />
     707        <field id="cldfraliq"    long_name="Fraction of liquid cloud"    unit="-" />
     708        <field id="sigma2_icefracturb"    long_name="Variance of the diagnostic supersaturation distribution (icefrac_turb)"    unit="-" />
     709        <field id="mean_icefracturb"     long_name="Mean of the diagnostic supersaturation distribution (icefrac_turb)"    unit="-" />
    690710        <field id="rnebcon"    long_name="Convective Cloud Fraction"    unit="-" />
    691711        <field id="rnebls"    long_name="LS Cloud fraction"    unit="-" />
  • LMDZ6/trunk/libf/phylmd/lmdz_lscp.F90

    r4915 r5007  
    77!++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    88SUBROUTINE lscp(klon,klev,dtime,missing_val,            &
    9      paprs,pplay,temp,qt,ptconv,ratqs,                  &
     9     paprs,pplay,temp,qt,qice_save,ptconv,ratqs,        &
    1010     d_t, d_q, d_ql, d_qi, rneb, rneblsvol, rneb_seri,  &
    11      pfraclr,pfracld,                                   &
     11     pfraclr, pfracld,                                  &
     12     cldfraliq, sigma2_icefracturb,mean_icefracturb,    &
    1213     radocond, radicefrac, rain, snow,                  &
    1314     frac_impa, frac_nucl, beta,                        &
    14      prfl, psfl, rhcl, qta, fraca,                     &
    15      tv, pspsk, tla, thl, iflag_cld_th,             &
     15     prfl, psfl, rhcl, qta, fraca,                      &
     16     tv, pspsk, tla, thl, iflag_cld_th,                 &
    1617     iflag_ice_thermo, ok_ice_sursat, qsatl, qsats,     &
    17      distcltop,temp_cltop,                              &
     18     distcltop, temp_cltop, tke, tke_dissip,            &
    1819     qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss,   &
    1920     Tcontr, qcontr, qcontr2, fcontrN, fcontrP,         &
     
    9697! USE de modules contenant des fonctions.
    9798USE lmdz_cloudth, ONLY : cloudth, cloudth_v3, cloudth_v6, cloudth_mpc
    98 USE lmdz_lscp_tools, ONLY : calc_qsat_ecmwf, icefrac_lscp, calc_gammasat
     99USE lmdz_lscp_tools, ONLY : calc_qsat_ecmwf, calc_gammasat
     100USE lmdz_lscp_tools, ONLY : icefrac_lscp, icefrac_lscp_turb
    99101USE lmdz_lscp_tools, ONLY : fallice_velocity, distance_to_cloud_top
    100102USE ice_sursat_mod, ONLY : ice_sursat
     
    111113USE lmdz_lscp_ini, ONLY : RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG
    112114USE lmdz_lscp_ini, ONLY : ok_poprecip
    113 
     115USE lmdz_lscp_ini, ONLY : iflag_icefrac
    114116IMPLICIT NONE
    115117
     
    129131  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: temp            ! temperature (K)
    130132  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: qt              ! total specific humidity (in vapor phase in input) [kg/kg]
     133  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: qice_save       ! ice specific from previous time step [kg/kg]
    131134  INTEGER,                         INTENT(IN)   :: iflag_cld_th    ! flag that determines the distribution of convective clouds
    132135  INTEGER,                         INTENT(IN)   :: iflag_ice_thermo! flag to activate the ice thermodynamics
     
    138141  !Inputs associated with thermal plumes
    139142
    140   REAL, DIMENSION(klon,klev),      INTENT(IN)   :: tv             ! virtual potential temperature [K]
    141   REAL, DIMENSION(klon,klev),      INTENT(IN)   :: qta            ! specific humidity within thermals [kg/kg]
    142   REAL, DIMENSION(klon,klev),      INTENT(IN)   :: fraca          ! fraction of thermals within the mesh [-]
    143   REAL, DIMENSION(klon,klev),      INTENT(IN)   :: pspsk          ! exner potential (p/100000)**(R/cp)
    144   REAL, DIMENSION(klon,klev),      INTENT(IN)   :: tla            ! liquid temperature within thermals [K]
     143  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: tv                  ! virtual potential temperature [K]
     144  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: qta                 ! specific humidity within thermals [kg/kg]
     145  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: fraca               ! fraction of thermals within the mesh [-]
     146  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: pspsk               ! exner potential (p/100000)**(R/cp)
     147  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: tla                 ! liquid temperature within thermals [K]
     148  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: tke                 !--turbulent kinetic energy [m2/s2]
     149  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: tke_dissip          !--TKE dissipation [m2/s3]
    145150
    146151  ! INPUT/OUTPUT variables
    147152  !------------------------
    148153 
    149   REAL, DIMENSION(klon,klev),      INTENT(INOUT)   :: thl          ! liquid potential temperature [K]
    150   REAL, DIMENSION(klon,klev),      INTENT(INOUT)   :: ratqs        ! function of pressure that sets the large-scale
     154  REAL, DIMENSION(klon,klev),      INTENT(INOUT)   :: thl              ! liquid potential temperature [K]
     155  REAL, DIMENSION(klon,klev),      INTENT(INOUT)   :: ratqs            ! function of pressure that sets the large-scale
    151156
    152157
    153158  ! Input sursaturation en glace
    154   REAL, DIMENSION(klon,klev),      INTENT(INOUT):: rneb_seri        ! fraction nuageuse en memoire
     159  REAL, DIMENSION(klon,klev),      INTENT(INOUT):: rneb_seri           ! fraction nuageuse en memoire
    155160 
    156161  ! OUTPUT variables
    157162  !-----------------
    158163
    159   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_t              ! temperature increment [K]
    160   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_q              ! specific humidity increment [kg/kg]
    161   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_ql             ! liquid water increment [kg/kg]
    162   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_qi             ! cloud ice mass increment [kg/kg]
    163   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rneb             ! cloud fraction [-]
    164   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rneblsvol        ! cloud fraction per unit volume [-] 
    165   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: pfraclr          ! precip fraction clear-sky part [-]
    166   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: pfracld          ! precip fraction cloudy part [-]
    167   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: radocond         ! condensed water used in the radiation scheme [kg/kg]
    168   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: radicefrac       ! ice fraction of condensed water for radiation scheme
    169   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rhcl             ! clear-sky relative humidity [-]
    170   REAL, DIMENSION(klon),           INTENT(OUT)  :: rain             ! surface large-scale rainfall [kg/s/m2]
    171   REAL, DIMENSION(klon),           INTENT(OUT)  :: snow             ! surface large-scale snowfall [kg/s/m2]
    172   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qsatl            ! saturation specific humidity wrt liquid [kg/kg]
    173   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qsats            ! saturation specific humidity wrt ice [kg/kg] 
    174   REAL, DIMENSION(klon,klev+1),    INTENT(OUT)  :: prfl             ! large-scale rainfall flux in the column [kg/s/m2]
    175   REAL, DIMENSION(klon,klev+1),    INTENT(OUT)  :: psfl             ! large-scale snowfall flux in the column [kg/s/m2]
    176   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: distcltop        ! distance to cloud top [m]
    177   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: temp_cltop       ! temperature of cloud top [K]
    178   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: beta             ! conversion rate of condensed water
    179 
    180   ! fraction of aerosol scavenging through impaction and nucleation (for on-line)
     164  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_t                 ! temperature increment [K]
     165  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_q                 ! specific humidity increment [kg/kg]
     166  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_ql                ! liquid water increment [kg/kg]
     167  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: d_qi                ! cloud ice mass increment [kg/kg]
     168  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rneb                ! cloud fraction [-]
     169  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rneblsvol           ! cloud fraction per unit volume [-] 
     170  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: pfraclr             ! precip fraction clear-sky part [-]
     171  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: pfracld             ! precip fraction cloudy part [-]
     172  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cldfraliq           ! liquid fraction of cloud [-]
     173  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: sigma2_icefracturb  ! Variance of the diagnostic supersaturation distribution (icefrac_turb) [-]
     174  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: mean_icefracturb    ! Mean of the diagnostic supersaturation distribution (icefrac_turb) [-]
     175  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: radocond            ! condensed water used in the radiation scheme [kg/kg]
     176  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: radicefrac          ! ice fraction of condensed water for radiation scheme
     177  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rhcl                ! clear-sky relative humidity [-]
     178  REAL, DIMENSION(klon),           INTENT(OUT)  :: rain                ! surface large-scale rainfall [kg/s/m2]
     179  REAL, DIMENSION(klon),           INTENT(OUT)  :: snow                ! surface large-scale snowfall [kg/s/m2]
     180  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qsatl               ! saturation specific humidity wrt liquid [kg/kg]
     181  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qsats               ! saturation specific humidity wrt ice [kg/kg] 
     182  REAL, DIMENSION(klon,klev+1),    INTENT(OUT)  :: prfl                ! large-scale rainfall flux in the column [kg/s/m2]
     183  REAL, DIMENSION(klon,klev+1),    INTENT(OUT)  :: psfl                ! large-scale snowfall flux in the column [kg/s/m2]
     184  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: distcltop           ! distance to cloud top [m]
     185  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: temp_cltop          ! temperature of cloud top [K]
     186  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: beta                ! conversion rate of condensed water
     187
     188  ! fraction of aerosol scavenging through impaction and nucleation    (for on-line)
    181189 
    182   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: frac_impa        ! scavenging fraction due tu impaction [-]
    183   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: frac_nucl        ! scavenging fraction due tu nucleation [-]
     190  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: frac_impa           ! scavenging fraction due tu impaction [-]
     191  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: frac_nucl           ! scavenging fraction due tu nucleation [-]
    184192 
    185193  ! for supersaturation and contrails parameterisation
    186194 
    187   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qclr             ! specific total water content in clear sky region [kg/kg]
    188   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qcld             ! specific total water content in cloudy region [kg/kg]
    189   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qss              ! specific total water content in supersat region [kg/kg]
    190   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qvc              ! specific vapor content in clouds [kg/kg]
    191   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rnebclr          ! mesh fraction of clear sky [-]   
    192   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rnebss           ! mesh fraction of ISSR [-] 
    193   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: gamma_ss         ! coefficient governing the ice nucleation RHi threshold [-]     
    194   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: Tcontr           ! threshold temperature for contrail formation [K]
    195   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qcontr           ! threshold humidity for contrail formation [kg/kg]
    196   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qcontr2          ! // (2nd expression more consistent with LMDZ expression of q)         
    197   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: fcontrN          ! fraction of grid favourable to non-persistent contrails
    198   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: fcontrP          ! fraction of grid favourable to persistent contrails
    199   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_sth      ! mean saturation deficit in thermals
    200   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_senv     ! mean saturation deficit in environment
    201   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_sigmath  ! std of saturation deficit in thermals
    202   REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_sigmaenv ! std of saturation deficit in environment
     195  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qclr                ! specific total water content in clear sky region [kg/kg]
     196  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qcld                ! specific total water content in cloudy region [kg/kg]
     197  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qss                 ! specific total water content in supersat region [kg/kg]
     198  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qvc                 ! specific vapor content in clouds [kg/kg]
     199  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rnebclr             ! mesh fraction of clear sky [-]   
     200  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: rnebss              ! mesh fraction of ISSR [-] 
     201  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: gamma_ss            ! coefficient governing the ice nucleation RHi threshold [-]     
     202  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: Tcontr              ! threshold temperature for contrail formation [K]
     203  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qcontr              ! threshold humidity for contrail formation [kg/kg]
     204  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: qcontr2             ! // (2nd expression more consistent with LMDZ expression of q)         
     205  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: fcontrN             ! fraction of grid favourable to non-persistent contrails
     206  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: fcontrP             ! fraction of grid favourable to persistent contrails
     207  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_sth         ! mean saturation deficit in thermals
     208  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_senv        ! mean saturation deficit in environment
     209  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_sigmath     ! std of saturation deficit in thermals
     210  REAL, DIMENSION(klon,klev),      INTENT(OUT)  :: cloudth_sigmaenv    ! std of saturation deficit in environment
    203211
    204212  ! for POPRECIP
     
    221229  ! LOCAL VARIABLES:
    222230  !----------------
    223 
    224   REAL,DIMENSION(klon) :: qsl, qsi
     231  REAL,DIMENSION(klon) :: qsl, qsi                                ! saturation threshold at current vertical level
    225232  REAL :: zct, zcl,zexpo
    226233  REAL, DIMENSION(klon,klev) :: ctot
     
    229236  REAL :: zdelta, zcor, zcvm5
    230237  REAL, DIMENSION(klon) :: zdqsdT_raw
    231   REAL, DIMENSION(klon) :: gammasat,dgammasatdt                ! coefficient to make cold condensation at the correct RH and derivative wrt T
    232   REAL, DIMENSION(klon) :: Tbef,qlbef,DT
     238  REAL, DIMENSION(klon) :: gammasat,dgammasatdt                   ! coefficient to make cold condensation at the correct RH and derivative wrt T
     239  REAL, DIMENSION(klon) :: Tbef,qlbef,DT                          ! temperature, humidity and temp. variation during lognormal iteration
    233240  REAL :: num,denom
    234241  REAL :: cste
    235   REAL, DIMENSION(klon) :: zpdf_sig,zpdf_k,zpdf_delta
    236   REAL, DIMENSION(klon) :: Zpdf_a,zpdf_b,zpdf_e1,zpdf_e2
     242  REAL, DIMENSION(klon) :: zpdf_sig,zpdf_k,zpdf_delta             ! lognormal parameters
     243  REAL, DIMENSION(klon) :: Zpdf_a,zpdf_b,zpdf_e1,zpdf_e2          ! lognormal intermediate variables
    237244  REAL :: erf
    238245  REAL, DIMENSION(klon) :: zfice_th
     
    251258  REAL :: zmelt,zrain,zsnow,zprecip
    252259  REAL, DIMENSION(klon) :: dzfice
     260  REAL, DIMENSION(klon) :: zfice_turb, dzfice_turb
    253261  REAL :: zsolid
    254262  REAL, DIMENSION(klon) :: qtot, qzero
     
    281289  REAL, DIMENSION(klon,klev) :: radocondi, radocondl
    282290  REAL :: effective_zneb
    283   REAL, DIMENSION(klon) :: distcltop1D, temp_cltop1D
    284 
     291  REAL, DIMENSION(klon) :: zdistcltop, ztemp_cltop
     292  REAL, DIMENSION(klon) :: zqliq, zqice, zqvapcl        ! for icefrac_lscp_turb
    285293
    286294  INTEGER i, k, n, kk, iter
     
    337345pfraclr(:,:)=0.0
    338346pfracld(:,:)=0.0
     347cldfraliq(:,:)=0.
     348sigma2_icefracturb(:,:)=0.
     349mean_icefracturb(:,:)=0.
    339350radocond(:,:) = 0.0
    340351radicefrac(:,:) = 0.0
     
    346357zfice(:)=0.0
    347358dzfice(:)=0.0
     359zfice_turb(:)=0.0
     360dzfice_turb(:)=0.0
    348361zqprecl(:)=0.0
    349362zqpreci(:)=0.0
     
    360373d_tot_zneb(:) = 0.0
    361374qzero(:) = 0.0
    362 distcltop1D(:)=0.0
    363 temp_cltop1D(:) = 0.0
     375zdistcltop(:)=0.0
     376ztemp_cltop(:) = 0.0
    364377ztupnew(:)=0.0
    365378!--ice supersaturation
     
    374387distcltop(:,:)=0.
    375388temp_cltop(:,:)=0.
     389
    376390!-- poprecip
    377391qraindiag(:,:)= 0.
     
    393407
    394408
    395 
    396409!c_iso: variable initialisation for iso
    397410
     
    412425
    413426    ! Initialisation temperature and specific humidity
     427    ! temp(klon,klev) is not modified by the routine, instead all changes in temperature are made on zt
     428    ! at the end of the klon loop, a temperature incremtent d_t due to all processes
     429    ! (thermalization, evap/sub incoming precip, cloud formation, precipitation processes) is calculated
     430    ! d_t = temperature tendency due to lscp
     431    ! The temperature of the overlying layer is updated here because needed for thermalization
    414432    DO i = 1, klon
    415433        zt(i)=temp(i,k)
     
    746764                ELSEIF (iflag_cloudth_vert .EQ. 7) THEN
    747765                   ! Updated version of Arnaud Jam (correction by E. Vignon) + adapted treatment
    748                    ! for boundary-layer mixed phase clouds following Vignon et al. 
     766                   ! for boundary-layer mixed phase clouds
    749767                    CALL cloudth_mpc(klon,klev,k,mpc_bl_points,zt,zq,qta(:,k),fraca(:,k), &
    750768                                     pspsk(:,k),paprs(:,k+1),paprs(:,k),pplay(:,k), tla(:,k), &
     
    766784           
    767785                ! lognormal
    768             lognormale = .TRUE.
     786            lognormale(:) = .TRUE.
    769787
    770788        ELSEIF (iflag_cld_th .GE. 6) THEN
    771789           
    772790                ! lognormal distribution when no thermals
    773             lognormale = fraca(:,k) < min_frac_th_cld
     791            lognormale(:) = fraca(:,k) < min_frac_th_cld
    774792
    775793        ELSE
    776794                ! When iflag_cld_th=5, we always assume
    777795                ! bi-gaussian distribution
    778             lognormale = .FALSE.
     796            lognormale(:) = .FALSE.
    779797       
    780798        ENDIF
     
    829847                  IF (iflag_t_glace.GE.4) THEN
    830848                  ! For iflag_t_glace GE 4 the phase partition function dependends on temperature AND distance to cloud top
    831                        CALL distance_to_cloud_top(klon,klev,k,temp,pplay,paprs,rneb,distcltop1D,temp_cltop1D)
     849                       CALL distance_to_cloud_top(klon,klev,k,temp,pplay,paprs,rneb,zdistcltop,ztemp_cltop)
    832850                  ENDIF
    833                   CALL icefrac_lscp(klon, zt(:), iflag_ice_thermo, distcltop1D(:),temp_cltop1D(:),zfice(:),dzfice(:))
     851
     852                  CALL icefrac_lscp(klon, zt(:), iflag_ice_thermo, zdistcltop(:),ztemp_cltop(:),zfice(:),dzfice(:))
    834853
    835854                  DO i=1,klon !todoan : check if loop in i is needed
     
    896915                            cste=RLSTT
    897916                        ENDIF
    898 
     917                       
     918                        ! LEA_R : check formule
    899919                        qlbef(i)=max(0.,zqn(i)-zqs(i))
    900920                        num = -Tbef(i)+zt(i)+rneb(i,k)*((1-zfice(i))*RLVTT &
     
    927947        ! For iflag_t_glace GE 4 the phase partition function dependends on temperature AND distance to cloud top
    928948        IF (iflag_t_glace.GE.4) THEN
    929             CALL distance_to_cloud_top(klon,klev,k,temp,pplay,paprs,rneb,distcltop1D,temp_cltop1D)
    930             distcltop(:,k)=distcltop1D(:)
    931             temp_cltop(:,k)=temp_cltop1D(:)
    932         ENDIF   
    933         ! Partition function in stratiform clouds (will be overwritten in boundary-layer MPCs)
    934         CALL icefrac_lscp(klon,zt,iflag_ice_thermo,distcltop1D,temp_cltop1D,zfice,dzfice)
    935 
     949           CALL distance_to_cloud_top(klon,klev,k,temp,pplay,paprs,rneb,zdistcltop,ztemp_cltop)
     950           distcltop(:,k)=zdistcltop(:)
     951           temp_cltop(:,k)=ztemp_cltop(:)
     952        ENDIF
     953
     954        ! Partition function depending on temperature
     955        CALL icefrac_lscp(klon, Tbef, iflag_ice_thermo, zdistcltop, ztemp_cltop, zfice, dzfice)
     956
     957        ! Partition function depending on tke for non shallow-convective clouds
     958        IF (iflag_icefrac .GE. 1) THEN
     959
     960           CALL icefrac_lscp_turb(klon, dtime, Tbef, pplay(:,k), paprs(:,k), paprs(:,k+1), qice_save(:,k), ziflcld, zqn, &
     961           rneb(:,k), tke(:,k), tke_dissip(:,k), zqliq, zqvapcl, zqice, zfice_turb, dzfice_turb, cldfraliq(:,k),sigma2_icefracturb(:,k), mean_icefracturb(:,k))
     962
     963        ENDIF
    936964
    937965        ! Water vapor update, Phase determination and subsequent latent heat exchange
    938966        DO i=1, klon
    939 
     967            ! Overwrite phase partitioning in boundary layer mixed phase clouds when the
     968            ! iflag_cloudth_vert=7 and specific param is activated
    940969            IF (mpc_bl_points(i,k) .GT. 0) THEN
    941                
    942970                zcond(i) = MAX(0.0,qincloud_mpc(i))*rneb(i,k)
    943971                ! following line is very strange and probably wrong
     
    946974                zq(i) = zq(i) - zcond(i)       
    947975                zfice(i)=zfice_th(i)
    948 
    949976            ELSE
    950 
    951977                ! Checks on rneb, rhcl and zqn
    952978                IF (rneb(i,k) .LE. 0.0) THEN
     
    964990                    ! following line is very strange and probably wrong:
    965991                    rhcl(i,k)=(zqs(i)+zq(i))/2./zqs(i)
     992                    ! Overwrite partitioning for non shallow-convective clouds if iflag_icefrac>1 (icefrac turb param)
     993                    IF (iflag_icefrac .GE. 1) THEN
     994                        IF (lognormale(i)) THEN 
     995                           zcond(i)  = zqliq(i) + zqice(i)
     996                           zfice(i)=zfice_turb(i)
     997                           rhcl(i,k) = zqvapcl(i) * rneb(i,k) + (zq(i) - zqn(i)) * (1.-rneb(i,k))
     998                        ENDIF
     999                    ENDIF
    9661000                ENDIF
    9671001
     
    13061340                znebprecipcld(i)=0.0
    13071341            ENDIF
    1308 
     1342        !IF ( ((1-zfice(i))*zoliq(i) .GT. 0.) .AND. (zt(i) .LE. 233.15) ) THEN
     1343        !print*,'WARNING LEA OLIQ A <-40°C '
     1344        !print*,'zt,Tbef,oliq,oice,cldfraliq,icefrac,rneb',zt(i),Tbef(i),(1-zfice(i))*zoliq(i),zfice(i)*zoliq(i),cldfraliq(i,k),zfice(i),rneb(i,k)
     1345        !ENDIF
    13091346        ENDDO
    13101347
  • LMDZ6/trunk/libf/phylmd/lmdz_lscp_ini.F90

    r4915 r5007  
    66  !--------------------
    77 
    8   REAL RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG, RPI
    9   !$OMP THREADPRIVATE(RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG, RPI)
     8  REAL RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG, RV, RPI
     9  !$OMP THREADPRIVATE(RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG, RV, RPI)
    1010 
    1111  REAL, SAVE, PROTECTED :: seuil_neb=0.001      ! cloud fraction threshold: a cloud can precipitate when exceeded
     
    6767  !$OMP THREADPRIVATE(iflag_t_glace)
    6868
    69   INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0         ! option for determining cloud fraction and content in convective boundary layers
     69  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0          ! option for determining cloud fraction and content in convective boundary layers
    7070  !$OMP THREADPRIVATE(iflag_cloudth_vert)
    7171
    72   INTEGER, SAVE, PROTECTED :: iflag_gammasat=0             ! which threshold for homogeneous nucleation below -40oC
     72  INTEGER, SAVE, PROTECTED :: iflag_gammasat=0              ! which threshold for homogeneous nucleation below -40oC
    7373  !$OMP THREADPRIVATE(iflag_gammasat)
    7474
    75   INTEGER, SAVE, PROTECTED :: iflag_rain_incloud_vol=0     ! use of volume cloud fraction for rain autoconversion
     75  INTEGER, SAVE, PROTECTED :: iflag_rain_incloud_vol=0      ! use of volume cloud fraction for rain autoconversion
    7676  !$OMP THREADPRIVATE(iflag_rain_incloud_vol)
    7777
    78   INTEGER, SAVE, PROTECTED :: iflag_bergeron=0             ! bergeron effect for liquid precipitation treatment 
     78  INTEGER, SAVE, PROTECTED :: iflag_bergeron=0              ! bergeron effect for liquid precipitation treatment 
    7979  !$OMP THREADPRIVATE(iflag_bergeron)
    8080
    81   INTEGER, SAVE, PROTECTED :: iflag_fisrtilp_qsat=0        ! qsat adjustment (iterative) during autoconversion
     81  INTEGER, SAVE, PROTECTED :: iflag_fisrtilp_qsat=0         ! qsat adjustment (iterative) during autoconversion
    8282  !$OMP THREADPRIVATE(iflag_fisrtilp_qsat)
    8383
    84   INTEGER, SAVE, PROTECTED :: iflag_pdf=0                  ! type of subgrid scale qtot pdf
     84  INTEGER, SAVE, PROTECTED :: iflag_pdf=0                   ! type of subgrid scale qtot pdf
    8585  !$OMP THREADPRIVATE(iflag_pdf)
    8686
    87   INTEGER, SAVE, PROTECTED :: iflag_autoconversion=0       ! autoconversion option
     87  INTEGER, SAVE, PROTECTED :: iflag_icefrac=0               ! which phase partitioning function to use
     88  !$OMP THREADPRIVATE(iflag_icefrac)
     89
     90  INTEGER, SAVE, PROTECTED :: iflag_autoconversion=0        ! autoconversion option
    8891  !$OMP THREADPRIVATE(iflag_autoconversion)
    8992
    90   LOGICAL, SAVE, PROTECTED :: reevap_ice=.false.           ! no liquid precip for T< threshold
     93
     94  LOGICAL, SAVE, PROTECTED :: reevap_ice=.false.            ! no liquid precip for T< threshold
    9195  !$OMP THREADPRIVATE(reevap_ice)
    9296
    93   REAL, SAVE, PROTECTED :: cld_lc_lsc=2.6e-4               ! liquid autoconversion coefficient, stratiform rain
     97  REAL, SAVE, PROTECTED :: cld_lc_lsc=2.6e-4                ! liquid autoconversion coefficient, stratiform rain
    9498  !$OMP THREADPRIVATE(cld_lc_lsc)
    9599
     
    118122  !$OMP THREADPRIVATE(coef_eva)
    119123
    120   REAL, SAVE, PROTECTED :: coef_sub                        ! tuning coefficient ice precip sublimation
     124  REAL, SAVE, PROTECTED :: coef_sub                         ! tuning coefficient ice precip sublimation
    121125  !$OMP THREADPRIVATE(coef_sub)
    122126
     
    124128  !$OMP THREADPRIVATE(expo_eva)
    125129
    126   REAL, SAVE, PROTECTED :: expo_sub                       ! tuning coefficient ice precip sublimation
     130  REAL, SAVE, PROTECTED :: expo_sub                         ! tuning coefficient ice precip sublimation
    127131  !$OMP THREADPRIVATE(expo_sub)
    128132
     
    158162  !$OMP THREADPRIVATE(thresh_precip_frac)
    159163
     164  REAL, SAVE, PROTECTED :: tau_mixenv=100000                ! Homogeneization time of mixed phase clouds [s]
     165  !$OMP THREADPRIVATE(tau_mixenv)
     166
     167    REAL, SAVE, PROTECTED :: capa_crystal=1.                ! Sursaturation of ice part in mixed phase clouds [-]
     168  !$OMP THREADPRIVATE(capa_crystal)
     169
     170  REAL, SAVE, PROTECTED :: lmix_mpc=1000                    ! Length of turbulent zones in Mixed Phase Clouds [m]
     171  !$OMP THREADPRIVATE(lmix_mpc)
     172
     173  REAL, SAVE, PROTECTED :: naero5=0.5                       ! Number concentration of aerosol larger than 0.5 microns [scm-3]
     174  !$OMP THREADPRIVATE(naero5)
     175
     176  REAL, SAVE, PROTECTED :: gamma_snwretro = 0.              ! Proportion of snow taken into account in ice retroaction in icefrac_turb [-]
     177  !$OMP THREADPRIVATE(gamma_snwretro)
     178
     179  REAL, SAVE, PROTECTED :: gamma_taud = 1.                  ! Tuning coeff for tau_dissipturb [-]
     180  !$OMP THREADPRIVATE(gamma_taud)
     181
    160182  REAL, SAVE, PROTECTED :: gamma_col=1.                     ! A COMMENTER TODO [-]
    161183  !$OMP THREADPRIVATE(gamma_col)
     
    167189  !$OMP THREADPRIVATE(gamma_rim)
    168190
    169   REAL, SAVE, PROTECTED :: rho_rain=1000.                    ! A COMMENTER TODO [kg/m3]
     191  REAL, SAVE, PROTECTED :: rho_rain=1000.                   ! Rain density [kg/m3]
    170192  !$OMP THREADPRIVATE(rho_rain)
    171193
    172   REAL, SAVE, PROTECTED :: rho_ice=920.                    ! A COMMENTER TODO [kg/m3]
     194  REAL, SAVE, PROTECTED :: rho_ice=920.                     ! Ice density [kg/m3]
    173195  !$OMP THREADPRIVATE(rho_ice)
    174196
    175   REAL, SAVE, PROTECTED :: r_rain=500.E-6                   ! A COMMENTER TODO [m]
     197  REAL, SAVE, PROTECTED :: r_rain=500.E-6                   ! Rain droplets radius for POPRECIP [m]
    176198  !$OMP THREADPRIVATE(r_rain)
    177199
    178   REAL, SAVE, PROTECTED :: r_snow=1.E-3                    ! A COMMENTER TODO [m]
     200  REAL, SAVE, PROTECTED :: r_snow=1.E-3                     ! Ice crystals radius for POPRECIP [m]
    179201  !$OMP THREADPRIVATE(r_snow)
    180202
    181   REAL, SAVE, PROTECTED :: tau_auto_snow_min=100.          ! A COMMENTER TODO [s]
     203  REAL, SAVE, PROTECTED :: tau_auto_snow_min=100.           ! A COMMENTER TODO [s]
    182204  !$OMP THREADPRIVATE(tau_auto_snow_min)
    183205
     
    188210  !$OMP THREADPRIVATE(eps)
    189211
    190   REAL, SAVE, PROTECTED :: gamma_melt=1.                   ! A COMMENTER TODO [-]
     212  REAL, SAVE, PROTECTED :: gamma_melt=1.                    ! A COMMENTER TODO [-]
    191213  !$OMP THREADPRIVATE(gamma_melt)
    192214
    193   REAL, SAVE, PROTECTED :: alpha_freez=4.                 ! A COMMENTER TODO [-]
     215  REAL, SAVE, PROTECTED :: alpha_freez=4.                   ! A COMMENTER TODO [-]
    194216  !$OMP THREADPRIVATE(alpha_freez)
    195217
    196   REAL, SAVE, PROTECTED :: beta_freez=0.1                 ! A COMMENTER TODO [m-3.s-1]
     218  REAL, SAVE, PROTECTED :: beta_freez=0.1                   ! A COMMENTER TODO [m-3.s-1]
    197219  !$OMP THREADPRIVATE(beta_freez)
    198220
    199   REAL, SAVE, PROTECTED :: gamma_freez=1.                 ! A COMMENTER TODO [-]
     221  REAL, SAVE, PROTECTED :: gamma_freez=1.                   ! A COMMENTER TODO [-]
    200222  !$OMP THREADPRIVATE(gamma_freez)
    201223
    202   REAL, SAVE, PROTECTED :: rain_fallspeed=4.              ! A COMMENTER TODO [m/s]
     224  REAL, SAVE, PROTECTED :: rain_fallspeed=4.                ! A COMMENTER TODO [m/s]
    203225  !$OMP THREADPRIVATE(rain_fallspeed)
    204226
    205   REAL, SAVE, PROTECTED :: rain_fallspeed_clr              ! A COMMENTER TODO [m/s]
     227  REAL, SAVE, PROTECTED :: rain_fallspeed_clr                ! A COMMENTER TODO [m/s]
    206228  !$OMP THREADPRIVATE(rain_fallspeed_clr)
    207229
    208   REAL, SAVE, PROTECTED :: rain_fallspeed_cld             ! A COMMENTER TODO [m/s]
     230  REAL, SAVE, PROTECTED :: rain_fallspeed_cld               ! A COMMENTER TODO [m/s]
    209231  !$OMP THREADPRIVATE(rain_fallspeed_cld)
    210232
    211   REAL, SAVE, PROTECTED :: snow_fallspeed=1.             ! A COMMENTER TODO [m/s]
     233  REAL, SAVE, PROTECTED :: snow_fallspeed=1.               ! A COMMENTER TODO [m/s]
    212234  !$OMP THREADPRIVATE(snow_fallspeed)
    213235
    214   REAL, SAVE, PROTECTED :: snow_fallspeed_clr             ! A COMMENTER TODO [m/s]
     236  REAL, SAVE, PROTECTED :: snow_fallspeed_clr               ! A COMMENTER TODO [m/s]
    215237  !$OMP THREADPRIVATE(snow_fallspeed_clr)
    216238
    217   REAL, SAVE, PROTECTED :: snow_fallspeed_cld             ! A COMMENTER TODO [m/s]
     239  REAL, SAVE, PROTECTED :: snow_fallspeed_cld               ! A COMMENTER TODO [m/s]
    218240  !$OMP THREADPRIVATE(snow_fallspeed_cld)
    219241  !--End of the parameters for poprecip
     
    226248
    227249SUBROUTINE lscp_ini(dtime,lunout_in,prt_level_in,ok_ice_sursat, iflag_ratqs, fl_cor_ebil_in, RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, &
    228                     RVTMP2_in, RTT_in,RD_in,RG_in,RPI_in)
     250                    RVTMP2_in, RTT_in,RD_in,RG_in,RV_in,RPI_in)
    229251
    230252
     
    238260
    239261   REAL, INTENT(IN)      :: RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in
    240    REAL, INTENT(IN)      ::  RVTMP2_in, RTT_in, RD_in, RG_in, RPI_in
     262   REAL, INTENT(IN)      ::  RVTMP2_in, RTT_in, RD_in, RG_in, RV_in, RPI_in
    241263   character (len=20) :: modname='lscp_ini_mod'
    242264   character (len=80) :: abort_message
     
    254276    RLMLT=RLMLT_in
    255277    RTT=RTT_in
    256     RG=RG_in
     278    RV=RV_in
    257279    RVTMP2=RVTMP2_in
    258280    RPI=RPI_in
     
    275297    CALL getin_p('iflag_fisrtilp_qsat',iflag_fisrtilp_qsat)
    276298    CALL getin_p('iflag_pdf',iflag_pdf)
     299    CALL getin_p('iflag_icefrac',iflag_icefrac)
    277300    CALL getin_p('reevap_ice',reevap_ice)
    278301    CALL getin_p('cld_lc_lsc',cld_lc_lsc)
     
    296319    CALL getin_p('dist_liq',dist_liq)
    297320    CALL getin_p('tresh_cl',tresh_cl)
     321    CALL getin_p('tau_mixenv',tau_mixenv)
     322    CALL getin_p('capa_crystal',capa_crystal)
     323    CALL getin_p('lmix_mpc',lmix_mpc)
     324    CALL getin_p('naero5',naero5)
     325    CALL getin_p('gamma_snwretro',gamma_snwretro)
     326    CALL getin_p('gamma_taud',gamma_taud)
    298327    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
    299328    CALL getin_p('ok_poprecip',ok_poprecip)
     
    334363    WRITE(lunout,*) 'lscp_ini, iflag_fisrtilp_qsat:', iflag_fisrtilp_qsat
    335364    WRITE(lunout,*) 'lscp_ini, iflag_pdf', iflag_pdf
     365    WRITE(lunout,*) 'lscp_ini, iflag_icefrac', iflag_icefrac
    336366    WRITE(lunout,*) 'lscp_ini, reevap_ice', reevap_ice
    337367    WRITE(lunout,*) 'lscp_ini, cld_lc_lsc', cld_lc_lsc
     
    352382    WRITE(lunout,*) 'lscp_ini, dist_liq', dist_liq
    353383    WRITE(lunout,*) 'lscp_ini, tresh_cl', tresh_cl
     384    WRITE(lunout,*) 'lscp_ini, tau_mixenv', tau_mixenv
     385    WRITE(lunout,*) 'lscp_ini, capa_crystal', capa_crystal
     386    WRITE(lunout,*) 'lscp_ini, lmix_mpc', lmix_mpc
     387    WRITE(lunout,*) 'lscp_ini, naero5', naero5
     388    WRITE(lunout,*) 'lscp_ini, gamma_snwretro', gamma_snwretro
     389    WRITE(lunout,*) 'lscp_ini, gamma_taud', gamma_taud
    354390    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
    355391    WRITE(lunout,*) 'lscp_ini, fl_cor_ebil', fl_cor_ebil
  • LMDZ6/trunk/libf/phylmd/lmdz_lscp_tools.F90

    r4818 r5007  
    136136    CHARACTER (len = 80) :: abort_message
    137137
    138     IF ((iflag_t_glace.LT.2) .OR. (iflag_t_glace.GT.6)) THEN
     138    IF ((iflag_t_glace.LT.2)) THEN !.OR. (iflag_t_glace.GT.6)) THEN
    139139       abort_message = 'lscp cannot be used if iflag_t_glace<2 or >6'
    140140       CALL abort_physic(modname,abort_message,1)
     
    194194
    195195        ! with CMIP6 function of temperature at cloud top
    196         IF (iflag_t_glace .EQ. 5) THEN
     196        IF ((iflag_t_glace .EQ. 5) .OR. (iflag_t_glace .EQ. 7)) THEN
    197197                liqfrac_tmp = (temp(i)-t_glace_min) / (t_glace_max-t_glace_min)
    198198                liqfrac_tmp =  MIN(MAX(liqfrac_tmp,0.0),1.0)
     
    232232                ENDIF
    233233        ENDIF
    234 
     234     
    235235
    236236     ENDDO ! klon
    237  
    238237     RETURN
    239238 
     
    241240!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    242241
     242SUBROUTINE ICEFRAC_LSCP_TURB(klon, dtime, temp, pplay, paprsdn, paprsup, qice_ini, snowcld, qtot_incl, cldfra, tke, tke_dissip, qliq, qvap_cld, qice, icefrac, dicefracdT, cldfraliq, sigma2_icefracturb, mean_icefracturb)
     243!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
     244  ! Compute the liquid, ice and vapour content (+ice fraction) based
     245  ! on turbulence (see Fields 2014, Furtado 2016)
     246!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
     247
     248
     249   USE lmdz_lscp_ini, ONLY : prt_level, lunout
     250   USE lmdz_lscp_ini, ONLY : RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG, RV, RPI
     251   USE lmdz_lscp_ini, ONLY : seuil_neb, temp_nowater
     252   USE lmdz_lscp_ini, ONLY : tau_mixenv, lmix_mpc, naero5, gamma_snwretro, gamma_taud, capa_crystal
     253   USE lmdz_lscp_ini, ONLY : eps
     254
     255   IMPLICIT NONE
     256
     257   INTEGER,   INTENT(IN)                           :: klon              !--number of horizontal grid points
     258   REAL,      INTENT(IN)                           :: dtime             !--time step [s]
     259
     260   REAL,      INTENT(IN),       DIMENSION(klon)    :: temp              !--temperature
     261   REAL,      INTENT(IN),       DIMENSION(klon)    :: pplay             !--pressure in the middle of the layer       [Pa]
     262   REAL,      INTENT(IN),       DIMENSION(klon)    :: paprsdn           !--pressure at the bottom interface of the layer [Pa]
     263   REAL,      INTENT(IN),       DIMENSION(klon)    :: paprsup           !--pressure at the top interface of the layer [Pa]
     264   REAL,      INTENT(IN),       DIMENSION(klon)    :: qtot_incl         !--specific total cloud water content, in-cloud content [kg/kg]
     265   REAL,      INTENT(IN),       DIMENSION(klon)    :: cldfra            !--cloud fraction in gridbox [-]
     266   REAL,      INTENT(IN),       DIMENSION(klon)    :: tke               !--turbulent kinetic energy [m2/s2]
     267   REAL,      INTENT(IN),       DIMENSION(klon)    :: tke_dissip        !--TKE dissipation [m2/s3]
     268
     269   REAL,      INTENT(IN),       DIMENSION(klon)    :: qice_ini          !--initial specific ice content gridbox-mean [kg/kg]
     270   REAL,      INTENT(IN),       DIMENSION(klon)    :: snowcld
     271   REAL,      INTENT(OUT),      DIMENSION(klon)    :: qliq              !--specific liquid content gridbox-mean [kg/kg]
     272   REAL,      INTENT(OUT),      DIMENSION(klon)    :: qvap_cld          !--specific cloud vapor content, gridbox-mean [kg/kg]
     273   REAL,      INTENT(OUT),      DIMENSION(klon)    :: qice              !--specific ice content gridbox-mean [kg/kg]
     274   REAL,      INTENT(OUT),      DIMENSION(klon)    :: icefrac           !--fraction of ice in condensed water [-]
     275   REAL,      INTENT(OUT),      DIMENSION(klon)    :: dicefracdT
     276
     277   REAL,      INTENT(OUT),      DIMENSION(klon)    :: cldfraliq         !--fraction of cldfra which is liquid only
     278   REAL,      INTENT(OUT),      DIMENSION(klon)    :: sigma2_icefracturb     !--Temporary
     279   REAL,      INTENT(OUT),      DIMENSION(klon)    :: mean_icefracturb      !--Temporary
     280
     281   REAL, DIMENSION(klon) :: qzero, qsatl, dqsatl, qsati, dqsati         !--specific humidity saturation values
     282   INTEGER :: i
     283
     284   REAL :: qvap_incl, qice_incl, qliq_incl, qiceini_incl                !--In-cloud specific quantities [kg/kg]
     285   REAL :: qsnowcld_incl
     286   !REAL :: capa_crystal                                                 !--Capacitance of ice crystals  [-]
     287   REAL :: water_vapor_diff                                             !--Water-vapour diffusion coefficient in air [m2/s] (function of T&P)
     288   REAL :: air_thermal_conduct                                          !--Thermal conductivity of air [J/m/K/s] (function of T)
     289   REAL :: C0                                                           !--Lagrangian structure function [-]
     290   REAL :: tau_mixingenv
     291   REAL :: tau_dissipturb
     292   REAL :: invtau_phaserelax
     293   REAL :: sigma2_pdf, mean_pdf
     294   REAL :: ai, bi, B0
     295   REAL :: sursat_iceliq
     296   REAL :: sursat_env
     297   REAL :: liqfra_max
     298   REAL :: sursat_iceext
     299   REAL :: nb_crystals                                                  !--number concentration of ice crystals [#/m3]
     300   REAL :: moment1_PSD                                                  !--1st moment of ice PSD
     301   REAL :: N0_PSD, lambda_PSD                                           !--parameters of the exponential PSD
     302
     303   REAL :: rho_ice                                                      !--ice density [kg/m3]
     304   REAL :: cldfra1D
     305   REAL :: deltaz, rho_air
     306   REAL :: psati                                                        !--saturation vapor pressure wrt i [Pa]
     307   
     308   C0            = 10.                                                  !--value assumed in Field2014           
     309   rho_ice       = 950.
     310   sursat_iceext = -0.1
     311   !capa_crystal  = 1. !r_ice                                       
     312   qzero(:)      = 0.
     313   cldfraliq(:)  = 0.
     314   icefrac(:)    = 0.
     315   dicefracdT(:) = 0.
     316
     317   sigma2_icefracturb(:) = 0.
     318   mean_icefracturb(:)  = 0.
     319
     320   !--wrt liquid water
     321   CALL calc_qsat_ecmwf(klon,temp(:),qzero(:),pplay(:),RTT,1,.false.,qsatl(:),dqsatl(:))
     322   !--wrt ice
     323   CALL calc_qsat_ecmwf(klon,temp(:),qzero(:),pplay(:),RTT,2,.false.,qsati(:),dqsati(:))
     324
     325
     326    DO i=1,klon
     327
     328
     329     rho_air  = pplay(i) / temp(i) / RD
     330     !deltaz   = ( paprsdn(i) - paprsup(i) ) / RG / rho_air(i)
     331     ! because cldfra is intent in, but can be locally modified due to test
     332     cldfra1D = cldfra(i)
     333     IF (cldfra(i) .LE. 0.) THEN
     334        qvap_cld(i)   = 0.
     335        qliq(i)       = 0.
     336        qice(i)       = 0.
     337        cldfraliq(i)  = 0.
     338        icefrac(i)    = 0.
     339        dicefracdT(i) = 0.
     340
     341     ! If there is a cloud
     342     ELSE
     343        IF (cldfra(i) .GE. 1.0) THEN
     344           cldfra1D = 1.0
     345        END IF
     346       
     347        ! T>0°C, no ice allowed
     348        IF ( temp(i) .GE. RTT ) THEN
     349           qvap_cld(i)   = qsatl(i) * cldfra1D
     350           qliq(i)       = MAX(0.0,qtot_incl(i)-qsatl(i))  * cldfra1D
     351           qice(i)       = 0.
     352           cldfraliq(i)  = 1.
     353           icefrac(i)    = 0.
     354           dicefracdT(i) = 0.
     355       
     356        ! T<-38°C, no liquid allowed
     357        ELSE IF ( temp(i) .LE. temp_nowater) THEN
     358           qvap_cld(i)   = qsati(i) * cldfra1D
     359           qliq(i)       = 0.
     360           qice(i)       = MAX(0.0,qtot_incl(i)-qsati(i)) * cldfra1D
     361           cldfraliq(i)  = 0.
     362           icefrac(i)    = 1.
     363           dicefracdT(i) = 0.
     364
     365        ! MPC temperature
     366        ELSE
     367           ! Not enough TKE     
     368           IF ( tke_dissip(i) .LE. eps )  THEN
     369              qvap_cld(i)   = qsati(i) * cldfra1D
     370              qliq(i)       = 0.
     371              qice(i)       = MAX(0.,qtot_incl(i)-qsati(i)) * cldfra1D   
     372              cldfraliq(i)  = 0.
     373              icefrac(i)    = 1.
     374              dicefracdT(i) = 0.
     375           
     376           ! Enough TKE   
     377           ELSE   
     378              !---------------------------------------------------------
     379              !--               ICE SUPERSATURATION PDF   
     380              !---------------------------------------------------------
     381              !--If -38°C< T <0°C and there is enough turbulence,
     382              !--we compute the cloud liquid properties with a Gaussian PDF
     383              !--of ice supersaturation F(Si) (Field2014, Furtado2016).
     384              !--Parameters of the PDF are function of turbulence and
     385              !--microphysics/existing ice.
     386
     387              sursat_iceliq = qsatl(i)/qsati(i) - 1.
     388              psati         = qsati(i) * pplay(i) / (RD/RV)
     389
     390              !-------------- MICROPHYSICAL TERMS --------------
     391              !--We assume an exponential ice PSD whose parameters
     392              !--are computed following Morrison&Gettelman 2008
     393              !--Ice number density is assumed equals to INP density
     394              !--which is a function of temperature (DeMott 2010) 
     395              !--bi and B0 are microphysical function characterizing
     396              !--vapor/ice interactions
     397              !--tau_phase_relax is the typical time of vapor deposition
     398              !--onto ice crystals
     399             
     400              qiceini_incl  = qice_ini(i) / cldfra1D
     401              qsnowcld_incl = snowcld(i) * RG * dtime / ( paprsdn(i) - paprsup(i) ) / cldfra1D
     402              sursat_env    = max(0., (qtot_incl(i) - qiceini_incl)/qsati(i) - 1.)
     403              IF ( qiceini_incl .GT. eps ) THEN
     404                nb_crystals = 1.e3 * 5.94e-5 * ( RTT - temp(i) )**3.33 * naero5**(0.0264*(RTT-temp(i))+0.0033)
     405                lambda_PSD  = ( (RPI*rho_ice*nb_crystals*24.) / (6.*(qiceini_incl + gamma_snwretro * qsnowcld_incl)) ) ** (1./3.)
     406                N0_PSD      = nb_crystals * lambda_PSD
     407                moment1_PSD = N0_PSD/2./lambda_PSD**2
     408              ELSE
     409                moment1_PSD = 0.
     410              ENDIF
     411
     412              !--Formulae for air thermal conductivity and water vapor diffusivity
     413              !--comes respectively from Beard and Pruppacher (1971)
     414              !--and  Hall and Pruppacher (1976)
     415
     416              air_thermal_conduct = ( 5.69 + 0.017 * ( temp(i) - RTT ) ) * 1.e-3 * 4.184
     417              water_vapor_diff    = 2.11*1e-5 * ( temp(i) / RTT )**1.94 * ( 101325 / pplay(i) )
     418             
     419              bi = 1./((qsati(i)+qsatl(i))/2.) + RLSTT**2 / RCPD / RV / temp(i)**2
     420              B0 = 4. * RPI * capa_crystal * 1. / (  RLSTT**2 / air_thermal_conduct / RV / temp(i)**2  &
     421                                                  +  RV * temp(i) / psati / water_vapor_diff  )
     422
     423              invtau_phaserelax  = (bi * B0 * moment1_PSD )
     424
     425!             Old way of estimating moment1 : spherical crystals + monodisperse PSD             
     426!             nb_crystals = rho_air * qiceini_incl / ( 4. / 3. * RPI * r_ice**3. * rho_ice )
     427!             moment1_PSD = nb_crystals * r_ice
     428
     429              !----------------- TURBULENT SOURCE/SINK TERMS -----------------
     430              !--Tau_mixingenv is the time needed to homogeneize the parcel
     431              !--with its environment by turbulent diffusion over the parcel
     432              !--length scale
     433              !--if lmix_mpc <0, tau_mixigenv value is prescribed
     434              !--else tau_mixigenv value is derived from tke_dissip and lmix_mpc
     435              !--Tau_dissipturb is the time needed turbulence to decay due to
     436              !--viscosity
     437
     438              ai = RG / RD / temp(i) * ( RD * RLSTT / RCPD / RV / temp(i) - 1. )
     439              IF ( lmix_mpc .GT. 0 ) THEN
     440                 tau_mixingenv = ( lmix_mpc**2. / tke_dissip(i) )**(1./3.)
     441              ELSE
     442                 tau_mixingenv = tau_mixenv
     443              ENDIF
     444             
     445              tau_dissipturb = gamma_taud * 2. * 2./3. * tke(i) / tke_dissip(i) / C0
     446
     447              !--------------------- PDF COMPUTATIONS ---------------------
     448              !--Formulae for sigma2_pdf (variance), mean of PDF in Furtado2016
     449              !--cloud liquid fraction and in-cloud liquid content are given
     450              !--by integrating resp. F(Si) and Si*F(Si)
     451              !--Liquid is limited by the available water vapor trough a
     452              !--maximal liquid fraction
     453
     454              liqfra_max = MAX(0., (MIN (1.,( qtot_incl(i) - qiceini_incl - qsati(i) * (1 + sursat_iceext ) ) / ( qsatl(i) - qsati(i) ) ) ) )
     455              sigma2_pdf = 1./2. * ( ai**2 ) *  2./3. * tke(i) * tau_dissipturb / ( invtau_phaserelax + 1./tau_mixingenv )
     456              mean_pdf   = sursat_env * 1./tau_mixingenv / ( invtau_phaserelax + 1./tau_mixingenv )
     457              cldfraliq(i) = 0.5 * (1. - erf( ( sursat_iceliq - mean_pdf) / (SQRT(2.* sigma2_pdf) ) ) )
     458              !IF (cldfraliq(i) .GT. liqfra_max) THEN
     459              !    cldfraliq(i) = liqfra_max
     460              !ENDIF
     461             
     462              qliq_incl = qsati(i) * SQRT(sigma2_pdf) / SQRT(2.*RPI) * EXP( -1.*(sursat_iceliq - mean_pdf)**2. / (2.*sigma2_pdf) )  &
     463                        - qsati(i) * cldfraliq(i) * (sursat_iceliq - mean_pdf )
     464             
     465              sigma2_icefracturb(i)= sigma2_pdf
     466              mean_icefracturb(i)  = mean_pdf     
     467              !------------ ICE AMOUNT AND WATER CONSERVATION  ------------
     468
     469              IF ( (qliq_incl .LE. eps) .OR. (cldfraliq(i) .LE. eps) ) THEN
     470                  qliq_incl    = 0.
     471                  cldfraliq(i) = 0.
     472              END IF
     473             
     474              !--Choice for in-cloud vapor :
     475              !--1.Weighted mean between qvap in MPC parts and in ice-only parts
     476              !--2.Always at ice saturation
     477              qvap_incl = MAX(qsati(i), ( 1. - cldfraliq(i) ) * (sursat_iceext + 1.) * qsati(i) + cldfraliq(i) * qsatl(i) )
     478               
     479              IF ( qvap_incl  .GE. qtot_incl(i) ) THEN
     480                 qvap_incl = qsati(i)
     481                 qliq_incl = qtot_incl(i) - qvap_incl
     482                 qice_incl = 0.
     483
     484              ELSEIF ( (qvap_incl + qliq_incl) .GE. qtot_incl(i) ) THEN
     485                 qliq_incl = MAX(0.0,qtot_incl(i) - qvap_incl)
     486                 qice_incl = 0.
     487              ELSE
     488                 qice_incl = qtot_incl(i) - qvap_incl - qliq_incl
     489              END IF
     490
     491              qvap_cld(i)   = qvap_incl * cldfra1D
     492              qliq(i)       = qliq_incl * cldfra1D
     493              qice(i)       = qice_incl * cldfra1D
     494              icefrac(i)    = qice(i) / ( qice(i) + qliq(i) )
     495              dicefracdT(i) = 0.
     496              !print*,'MPC turb'
     497
     498           END IF ! Enough TKE
     499
     500        END IF ! ! MPC temperature
     501
     502     END IF ! cldfra
     503   
     504   ENDDO ! klon
     505END SUBROUTINE ICEFRAC_LSCP_TURB
     506!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    243507
    244508
  • LMDZ6/trunk/libf/phylmd/phys_local_var_mod.F90

    r4998 r5007  
    478478      REAL, ALLOCATABLE, SAVE, DIMENSION(:,:) :: pfraclr,pfracld
    479479!$OMP THREADPRIVATE(pfraclr,pfracld)
     480      REAL, SAVE, ALLOCATABLE :: cldfraliq(:,:)
     481!$OMP THREADPRIVATE(cldfraliq)
     482      REAL, SAVE, ALLOCATABLE ::mean_icefracturb(:,:)
     483!$OMP THREADPRIVATE(mean_icefracturb)
     484      REAL, SAVE, ALLOCATABLE :: sigma2_icefracturb(:,:)
     485!$OMP THREADPRIVATE(sigma2_icefracturb)
    480486
    481487! variables de sorties MM
     
    957963      ALLOCATE(pfraclr(klon,klev),pfracld(klon,klev))
    958964      pfraclr(:,:)=0. ; pfracld(:,:)=0. ! because not always defined
     965      ALLOCATE(cldfraliq(klon,klev))
     966      ALLOCATE(sigma2_icefracturb(klon,klev))
     967      ALLOCATE(mean_icefracturb(klon,klev))
    959968      ALLOCATE(distcltop(klon,klev))
    960969      ALLOCATE(temp_cltop(klon,klev))
     
    12831292      DEALLOCATE(rneb)
    12841293      DEALLOCATE(pfraclr,pfracld)
     1294      DEALLOCATE(cldfraliq)
     1295      DEALLOCATE(sigma2_icefracturb)
     1296      DEALLOCATE(mean_icefracturb)
    12851297      DEALLOCATE (zxsnow,snowhgt,qsnow,to_ice,sissnow,runoff,albsol3_lic)
    12861298      DEALLOCATE(distcltop)
  • LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r4998 r5007  
    15591559  TYPE(ctrl_out), SAVE :: o_rneb = ctrl_out((/ 2, 5, 10, 10, 10, 10, 11, 11, 11, 11/), &
    15601560    'rneb', 'Cloud fraction', '-', (/ ('', i=1, 10) /))
     1561  TYPE(ctrl_out), SAVE :: o_cldfraliq = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     1562    'cldfraliq', 'Liquid fraction of the cloud', '-', (/ ('', i=1, 10) /))
     1563  TYPE(ctrl_out), SAVE :: o_sigma2_icefracturb = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     1564    'sigma2_icefracturb', 'Variance of the diagnostic supersaturation distribution (icefrac_turb) [-]', '-', (/ ('', i=1, 10) /))
     1565  TYPE(ctrl_out), SAVE :: o_mean_icefracturb = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     1566    'mean_icefracturb', 'Mean of the diagnostic supersaturation distribution (icefrac_turb) [-]', '-', (/ ('', i=1, 10) /))
     1567 
    15611568  TYPE(ctrl_out), SAVE :: o_rnebjn = ctrl_out((/ 2, 5, 10, 10, 10, 10, 11, 11,11, 11/), &     
    15621569    'rnebjn', 'Cloud fraction in day', '-', (/ ('', i=1, 10) /))
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4998 r5007  
    140140         o_zfull, o_zhalf, o_rneb, o_rnebjn, o_rnebcon, &
    141141         o_rnebls, o_rneblsvol, o_rhum, o_rhl, o_rhi, o_ozone, o_ozone_light, &
    142          o_pfraclr, o_pfracld, &
     142         o_pfraclr, o_pfracld, o_cldfraliq, o_sigma2_icefracturb, o_mean_icefracturb,  &
    143143         o_qrainlsc, o_qsnowlsc, o_dqreva, o_dqrauto, o_dqrcol, o_dqrmelt, o_dqrfreez, &
    144144         o_dqssub, o_dqsauto, o_dqsagg, o_dqsrim, o_dqsmelt, o_dqsfreez, &
     
    363363         ql_seri, qs_seri, qbs_seri, tr_seri, qbs_seri,&
    364364         zphi, u_seri, v_seri, omega, cldfra, &
    365          rneb, rnebjn, rneblsvol, zx_rh, zx_rhl, zx_rhi, &
    366          pfraclr, pfracld,  &
     365         rneb, rnebjn, rneblsvol,  &
     366         zx_rh, zx_rhl, zx_rhi, &
     367         pfraclr, pfracld, cldfraliq, sigma2_icefracturb, mean_icefracturb, &
    367368         qraindiag, qsnowdiag, dqreva, dqssub, &
    368369         dqrauto,dqrcol,dqrmelt,dqrfreez, &
     
    19992000           CALL histwrite_phy(o_pfraclr, pfraclr)
    20002001           CALL histwrite_phy(o_pfracld, pfracld)
     2002           CALL histwrite_phy(o_cldfraliq, cldfraliq)
     2003           CALL histwrite_phy(o_sigma2_icefracturb, sigma2_icefracturb)
     2004           CALL histwrite_phy(o_mean_icefracturb, mean_icefracturb)
    20012005           IF (ok_poprecip) THEN
    20022006           CALL histwrite_phy(o_qrainlsc, qraindiag)
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4976 r5007  
    332332       !
    333333       rneblsvol, &
    334        pfraclr,pfracld, &
    335        distcltop,temp_cltop, &
     334       pfraclr, pfracld, cldfraliq, sigma2_icefracturb, mean_icefracturb, &
     335       distcltop, temp_cltop, &
    336336       zqsatl, zqsats, &
    337337       qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss, &
     
    18631863   &    RG,RD,RCPD,RKAPPA,RLVTT,RETV)
    18641864       CALL ratqs_ini(klon,klev,iflag_thermals,lunout,nbsrf,is_lic,is_ter,RG,RV,RD,RCPD,RLSTT,RLVTT,RTT)
    1865        CALL lscp_ini(pdtphys,lunout,prt_level,ok_ice_sursat,iflag_ratqs,fl_cor_ebil,RCPD,RLSTT,RLVTT,RLMLT,RVTMP2,RTT,RD,RG,RPI)
     1865       CALL lscp_ini(pdtphys,lunout,prt_level,ok_ice_sursat,iflag_ratqs,fl_cor_ebil,RCPD,RLSTT,RLVTT,RLMLT,RVTMP2,RTT,RD,RG,RV,RPI)
    18661866       CALL blowing_snow_ini(RCPD, RLSTT, RLVTT, RLMLT, &
    18671867                             RVTMP2, RTT,RD,RG, RV, RPI)
     
    19431943       ELSE IF (klon_glo==1) THEN
    19441944          pbl_tke(:,:,is_ave) = 0.
     1945          pbl_eps(:,:,is_ave) = 0.
    19451946          DO nsrf=1,nbsrf
    19461947            DO k = 1,klev+1
    19471948                 pbl_tke(:,k,is_ave) = pbl_tke(:,k,is_ave) &
    19481949                     +pctsrf(:,nsrf)*pbl_tke(:,k,nsrf)
     1950                 pbl_eps(:,k,is_ave) = pbl_eps(:,k,is_ave) &
     1951                     +pctsrf(:,nsrf)*pbl_eps(:,k,nsrf)
    19491952            ENDDO
    19501953          ENDDO
     
    19521955          pbl_tke(:,:,is_ave) = 0. !ym missing init : maybe must be initialized in the same way that for klon_glo==1 ??
    19531956!>jyg
     1957          pbl_eps(:,:,is_ave) = 0.
    19541958       ENDIF
    19551959       !IM begin
     
    38963900
    38973901    CALL lscp(klon,klev,phys_tstep,missing_val,paprs,pplay, &
    3898          t_seri, q_seri,ptconv,ratqs, &
     3902         t_seri, q_seri,qs_ancien,ptconv,ratqs, &
    38993903         d_t_lsc, d_q_lsc, d_ql_lsc, d_qi_lsc, rneb, rneblsvol, rneb_seri, &
    3900          pfraclr,pfracld, &
     3904         pfraclr, pfracld, cldfraliq, sigma2_icefracturb, mean_icefracturb, &
    39013905         radocond, picefra, rain_lsc, snow_lsc, &
    39023906         frac_impa, frac_nucl, beta_prec_fisrt, &
    39033907         prfl, psfl, rhcl,  &
    39043908         zqasc, fraca,ztv,zpspsk,ztla,zthl,iflag_cld_th, &
    3905          iflag_ice_thermo, ok_ice_sursat, zqsatl, zqsats, distcltop, temp_cltop, &
    3906          qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss, &
     3909         iflag_ice_thermo, ok_ice_sursat, zqsatl, zqsats, distcltop, temp_cltop,  &
     3910         pbl_tke(:,:,is_ave), pbl_eps(:,:,is_ave), qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss, &
    39073911         Tcontr, qcontr, qcontr2, fcontrN, fcontrP , &
    39083912         cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv, &
  • LMDZ6/trunk/libf/phylmdiso/phys_local_var_mod.F90

    r4982 r5007  
    608608      REAL, ALLOCATABLE, SAVE, DIMENSION(:,:) :: pfraclr,pfracld
    609609!$OMP THREADPRIVATE(pfraclr,pfracld)
     610      REAL, SAVE, ALLOCATABLE :: cldfraliq(:,:)
     611!$OMP THREADPRIVATE(cldfraliq)
     612      REAL, SAVE, ALLOCATABLE ::mean_icefracturb(:,:)
     613!$OMP THREADPRIVATE(mean_icefracturb)
     614      REAL, SAVE, ALLOCATABLE :: sigma2_icefracturb(:,:)
     615!$OMP THREADPRIVATE(sigma2_icefracturb)
    610616
    611617! variables de sorties MM
     
    11561162      ALLOCATE(pfraclr(klon,klev),pfracld(klon,klev))
    11571163      pfraclr(:,:)=0. ; pfracld(:,:)=0. ! because not always defined
     1164      ALLOCATE(cldfraliq(klon,klev))
     1165      ALLOCATE(sigma2_icefracturb(klon,klev))
     1166      ALLOCATE(mean_icefracturb(klon,klev))
    11581167      ALLOCATE(distcltop(klon,klev))
    11591168      ALLOCATE(temp_cltop(klon,klev))
     
    15431552      DEALLOCATE(rneb)
    15441553      DEALLOCATE(pfraclr,pfracld)
     1554      DEALLOCATE(cldfraliq)
     1555      DEALLOCATE(sigma2_icefracturb)
     1556      DEALLOCATE(mean_icefracturb)
    15451557      DEALLOCATE (zxsnow,snowhgt,qsnow,to_ice,sissnow,runoff,albsol3_lic)
    15461558      DEALLOCATE(distcltop)
  • LMDZ6/trunk/libf/phylmdiso/phys_output_ctrlout_mod.F90

    r4889 r5007  
    15531553  TYPE(ctrl_out), SAVE :: o_rneb = ctrl_out((/ 2, 5, 10, 10, 10, 10, 11, 11, 11, 11/), &
    15541554    'rneb', 'Cloud fraction', '-', (/ ('', i=1, 10) /))
     1555  TYPE(ctrl_out), SAVE :: o_cldfraliq = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     1556    'cldfraliq', 'Liquid fraction of the cloud', '-', (/ ('', i=1, 10) /))
     1557  TYPE(ctrl_out), SAVE :: o_sigma2_icefracturb = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     1558    'sigma2_icefracturb', 'Variance of the diagnostic supersaturation distribution (icefrac_turb) [-]', '-', (/ ('', i=1, 10) /))
     1559  TYPE(ctrl_out), SAVE :: o_mean_icefracturb = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     1560    'mean_icefracturb', 'Mean of the diagnostic supersaturation distribution (icefrac_turb) [-]', '-', (/ ('', i=1, 10) /))
     1561 
    15551562  TYPE(ctrl_out), SAVE :: o_rnebjn = ctrl_out((/ 2, 5, 10, 10, 10, 10, 11, 11,11, 11/), &     
    15561563    'rnebjn', 'Cloud fraction in day', '-', (/ ('', i=1, 10) /))
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r4983 r5007  
    373373       !
    374374       rneblsvol, &
    375        pfraclr,pfracld, &
    376        distcltop,temp_cltop, &
     375       pfraclr, pfracld, cldfraliq, sigma2_icefracturb, mean_icefracturb, &
     376       distcltop, temp_cltop, &
    377377       zqsatl, zqsats, &
    378378       qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss, &
     
    20262026   &    RG,RD,RCPD,RKAPPA,RLVTT,RETV)
    20272027       CALL ratqs_ini(klon,klev,iflag_thermals,lunout,nbsrf,is_lic,is_ter,RG,RV,RD,RCPD,RLSTT,RLVTT,RTT)
    2028        CALL lscp_ini(pdtphys,lunout,prt_level,ok_ice_sursat,iflag_ratqs,fl_cor_ebil,RCPD,RLSTT,RLVTT,RLMLT,RVTMP2,RTT,RD,RG,RPI)
     2028       CALL lscp_ini(pdtphys,lunout,prt_level,ok_ice_sursat,iflag_ratqs,fl_cor_ebil,RCPD,RLSTT,RLVTT,RLMLT,RVTMP2,RTT,RD,RG,RV,RPI)
    20292029       CALL blowing_snow_ini(RCPD, RLSTT, RLVTT, RLMLT, &
    20302030                             RVTMP2, RTT,RD,RG, RV, RPI)
     
    50765076
    50775077    CALL lscp(klon,klev,phys_tstep,missing_val,paprs,pplay, &
    5078          t_seri, q_seri,ptconv,ratqs, &
     5078         t_seri, q_seri,qs_ancien,ptconv,ratqs, &
    50795079         d_t_lsc, d_q_lsc, d_ql_lsc, d_qi_lsc, rneb, rneblsvol, rneb_seri, &
    5080          pfraclr,pfracld, &
     5080         pfraclr, pfracld, cldfraliq, sigma2_icefracturb, mean_icefracturb, &
    50815081         radocond, picefra, rain_lsc, snow_lsc, &
    50825082         frac_impa, frac_nucl, beta_prec_fisrt, &
    50835083         prfl, psfl, rhcl,  &
    50845084         zqasc, fraca,ztv,zpspsk,ztla,zthl,iflag_cld_th, &
    5085          iflag_ice_thermo, ok_ice_sursat, zqsatl, zqsats, distcltop, temp_cltop, &
    5086          qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss, &
     5085         iflag_ice_thermo, ok_ice_sursat, zqsatl, zqsats, distcltop, temp_cltop,  &
     5086         pbl_tke(:,:,is_ave), pbl_eps(:,:,is_ave), qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss, &
    50875087         Tcontr, qcontr, qcontr2, fcontrN, fcontrP , &
    50885088         cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv, &
Note: See TracChangeset for help on using the changeset viewer.