Ignore:
Timestamp:
Apr 14, 2025, 9:21:07 PM (8 weeks ago)
Author:
evignon
Message:

Commission liée à un update majeur de la routine de condensation grande echelle suite au travail
de Lea, Audran et Etienne
Elle inclue une restructuration des routines pour clarifier le role "moniteur" de la routine lscp_main,
une mise à jour de la parametrisation de partitionnement de phase de Lea pour inclure les nuages de couche limite,
ainsi que des corrections des routines de precipitations "poprecip".
Convergence numerique verifiee en prod et debug pour les physiques NPv6.3 et 7.0.1c

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/lmdz_lscp_ini.f90

    r5437 r5614  
    99  !$OMP THREADPRIVATE(RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RV, RG, RPI, EPS_W)
    1010 
    11   REAL, SAVE, PROTECTED :: seuil_neb=0.001      ! cloud fraction threshold: a cloud can precipitate when exceeded
     11  INTEGER, SAVE, PROTECTED :: iflag_ratqs        ! control of ratqs option
     12  !$OMP THREADPRIVATE(iflag_ratqs)
     13 
     14  REAL, SAVE, PROTECTED :: seuil_neb=0.001       ! cloud fraction threshold: a cloud can precipitate when exceeded
    1215  !$OMP THREADPRIVATE(seuil_neb)
    1316
     
    6770  !$OMP THREADPRIVATE(iflag_t_glace)
    6871
    69   INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0          ! option for determining cloud fraction and content in convective boundary layers
    70   !$OMP THREADPRIVATE(iflag_cloudth_vert)
    71 
    7272  INTEGER, SAVE, PROTECTED :: iflag_gammasat=0              ! which threshold for homogeneous nucleation below -40oC
    7373  !$OMP THREADPRIVATE(iflag_gammasat)
     
    133133  !$OMP THREADPRIVATE(expo_sub)
    134134
    135   REAL, SAVE, PROTECTED :: cice_velo=1.645                  ! factor in the ice fall velocity formulation
     135  REAL, SAVE, PROTECTED :: cice_velo=1.645                  ! factor in the ice fall velocity formulation. It is half the value of
     136                                                            ! Heymsfield and Donner 1990 to concur with previous LMDZ versions
    136137  !$OMP THREADPRIVATE(cice_velo)
    137138
     
    205206  !--End of the parameters for condensation and ice supersaturation
    206207
    207   !--Parameters for poprecip
     208  !--Parameters for poprecip and cloud phase
    208209  LOGICAL, SAVE, PROTECTED :: ok_poprecip=.FALSE.           ! use the processes-oriented formulation of precipitations
    209210  !$OMP THREADPRIVATE(ok_poprecip)
     
    212213  !$OMP THREADPRIVATE(ok_corr_vap_evasub)
    213214
     215  LOGICAL, SAVE, PROTECTED :: ok_growth_precip_deposition=.FALSE. ! allows growth of snowfall through vapor deposition in supersat. regions
     216  !$OMP THREADPRIVATE(ok_growth_precip_deposition)
     217
    214218  REAL, SAVE, PROTECTED :: cld_lc_lsc_snow=2.e-5            ! snow autoconversion coefficient, stratiform. default from  Chaboureau and PInty 2006
    215219  !$OMP THREADPRIVATE(cld_lc_lsc_snow)
     
    233237  !$OMP THREADPRIVATE(gamma_snwretro)
    234238
     239  REAL, SAVE, PROTECTED :: gamma_mixth = 1.                 ! Tuning coeff for mixing with thermals/env in lscp_icefrac_turb [-]
     240  !$OMP THREADPRIVATE(gamma_mixth)
     241
    235242  REAL, SAVE, PROTECTED :: gamma_taud = 1.                  ! Tuning coeff for Lagrangian decorrelation timescale in lscp_icefrac_turb [-]
    236243  !$OMP THREADPRIVATE(gamma_taud)
     
    254261  !$OMP THREADPRIVATE(rho_rain)
    255262
    256   REAL, SAVE, PROTECTED :: rho_ice=920.                     ! Ice density [kg/m3]
     263  REAL, SAVE, PROTECTED :: rho_ice=920.                     ! Ice crystal density (assuming spherical geometry) [kg/m3]
    257264  !$OMP THREADPRIVATE(rho_ice)
    258265
     
    268275  REAL, SAVE, PROTECTED :: tau_auto_snow_max=1000.          ! Snow autoconversion minimal timescale (when only ice) [s]
    269276  !$OMP THREADPRIVATE(tau_auto_snow_max)
     277
     278  REAL, SAVE, PROTECTED :: expo_tau_auto_snow=0.1          ! Snow autoconversion timescale exponent for icefrac dependency
     279  !$OMP THREADPRIVATE(expo_tau_auto_snow)
    270280
    271281  REAL, SAVE, PROTECTED :: eps=1.E-10                       ! Treshold 0 [-]
     
    297307  !--End of the parameters for poprecip
    298308
    299 ! Two parameters used for lmdz_lscp_old only
     309  ! Parameters for cloudth routines
     310  LOGICAL, SAVE, PROTECTED :: ok_lscp_mergecond=.false.     ! more consistent condensation stratiform and shallow convective clouds
     311  !$OMP THREADPRIVATE(ok_lscp_mergecond)
     312 
     313  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert=0          ! option for determining cloud fraction and content in convective boundary layers
     314  !$OMP THREADPRIVATE(iflag_cloudth_vert)
     315
     316  INTEGER, SAVE, PROTECTED :: iflag_cloudth_vert_noratqs=0  ! option to control the width of gaussian distrib in a specific case
     317  !$OMP THREADPRIVATE(iflag_cloudth_vert_noratqs)
     318
     319  REAL, SAVE, PROTECTED :: cloudth_ratqsmin=-1.             ! minimum ratqs in cloudth
     320  !$OMP THREADPRIVATE(cloudth_ratqsmin)
     321
     322  REAL, SAVE, PROTECTED :: sigma1s_factor=1.1               ! factor for standard deviation of gaussian distribution of environment
     323  !$OMP THREADPRIVATE(sigma1s_factor)
     324
     325  REAL, SAVE, PROTECTED :: sigma2s_factor=0.09              ! factor for standard deviation of gaussian distribution of thermals
     326  !$OMP THREADPRIVATE(sigma2s_factor)
     327
     328
     329  REAL, SAVE, PROTECTED :: sigma1s_power=0.6                ! exponent for standard deviation of gaussian distribution of environment
     330  !$OMP THREADPRIVATE(sigma1s_power)
     331   
     332  REAL, SAVE, PROTECTED :: sigma2s_power=0.5                ! exponent for standard deviation of gaussian distribution of thermals
     333  !$OMP THREADPRIVATE(sigma2s_power)
     334
     335  REAL, SAVE, PROTECTED :: vert_alpha=0.5                   ! tuning coefficient for standard deviation of gaussian distribution of thermals
     336  !$OMP THREADPRIVATE(vert_alpha)
     337
     338  REAL, SAVE, PROTECTED :: vert_alpha_th=0.5                ! tuning coefficient for standard deviation of gaussian distribution of thermals
     339  !$OMP THREADPRIVATE(vert_alpha_th)
     340  ! End of parameters for cloudth routines
     341
     342  ! Two parameters used for lmdz_lscp_old only
    300343  INTEGER, SAVE, PROTECTED :: iflag_oldbug_fisrtilp=0, fl_cor_ebil
    301344  !$OMP THREADPRIVATE(iflag_oldbug_fisrtilp,fl_cor_ebil)
     
    303346CONTAINS
    304347
    305 SUBROUTINE lscp_ini(dtime,lunout_in,prt_level_in,ok_ice_supersat_in, iflag_ratqs, fl_cor_ebil_in, &
     348SUBROUTINE lscp_ini(dtime,lunout_in,prt_level_in,ok_ice_supersat_in, iflag_ratqs_in, fl_cor_ebil_in, &
    306349                    RCPD_in, RLSTT_in, RLVTT_in, RLMLT_in, RVTMP2_in, &
    307350                    RTT_in, RD_in, RV_in, RG_in, RPI_in, EPS_W_in)
     
    309352
    310353   USE ioipsl_getin_p_mod, ONLY : getin_p
    311    USE lmdz_cloudth_ini, ONLY : cloudth_ini
    312354
    313355   REAL, INTENT(IN)      :: dtime
    314    INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs,fl_cor_ebil_in
     356   INTEGER, INTENT(IN)   :: lunout_in,prt_level_in,iflag_ratqs_in,fl_cor_ebil_in
    315357   LOGICAL, INTENT(IN)   :: ok_ice_supersat_in
    316358
     
    324366    prt_level=prt_level_in
    325367    fl_cor_ebil=fl_cor_ebil_in
    326 
     368    iflag_ratqs=iflag_ratqs_in
    327369    ok_ice_supersat=ok_ice_supersat_in
    328370
     
    351393    CALL getin_p('iflag_vice',iflag_vice)
    352394    CALL getin_p('iflag_t_glace',iflag_t_glace)
    353     CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
    354395    CALL getin_p('iflag_gammasat',iflag_gammasat)
    355396    CALL getin_p('iflag_rain_incloud_vol',iflag_rain_incloud_vol)
     
    369410    CALL getin_p('ffallv_lsc',ffallv_lsc)
    370411    CALL getin_p('ffallv_lsc',ffallv_con)
     412    ! for poprecip and cloud phase
    371413    CALL getin_p('coef_eva',coef_eva)
    372414    coef_sub=coef_eva
     
    383425    CALL getin_p('gamma_snwretro',gamma_snwretro)
    384426    CALL getin_p('gamma_taud',gamma_taud)
     427    CALL getin_p('gamma_mixth',gamma_mixth)
    385428    CALL getin_p('iflag_oldbug_fisrtilp',iflag_oldbug_fisrtilp)
    386429    CALL getin_p('temp_nowater',temp_nowater)
    387430    CALL getin_p('ok_bug_phase_lscp',ok_bug_phase_lscp)
    388     ! for poprecip
    389431    CALL getin_p('ok_poprecip',ok_poprecip)
    390432    CALL getin_p('ok_corr_vap_evasub',ok_corr_vap_evasub)
     433    CALL getin_p('ok_growth_precip_deposition',ok_growth_precip_deposition)
    391434    CALL getin_p('rain_int_min',rain_int_min)
    392435    CALL getin_p('gamma_agg',gamma_agg)
     
    397440    CALL getin_p('tau_auto_snow_max',tau_auto_snow_max)
    398441    CALL getin_p('tau_auto_snow_min',tau_auto_snow_min)
     442    CALL getin_p('expo_tau_auto_snow', expo_tau_auto_snow)
     443    CALL getin_p('alpha_freez',alpha_freez)
     444    CALL getin_p('beta_freez',beta_freez)
    399445    CALL getin_p('r_snow',r_snow)
    400446    CALL getin_p('rain_fallspeed',rain_fallspeed)
     
    427473    CALL getin_p('coef_shear_lscp',coef_shear_lscp)
    428474    CALL getin_p('chi_mixing_lscp',chi_mixing_lscp)
    429 
    430 
     475    ! for cloudth routines
     476    CALL getin_p('ok_lscp_mergecond',ok_lscp_mergecond)
     477    CALL getin_p('iflag_cloudth_vert',iflag_cloudth_vert)
     478    CALL getin_p('cloudth_ratqsmin',cloudth_ratqsmin)
     479    CALL getin_p('cloudth_sigma1s_factor',sigma1s_factor)
     480    CALL getin_p('cloudth_sigma1s_power',sigma1s_power)
     481    CALL getin_p('cloudth_sigma2s_factor',sigma2s_factor)
     482    CALL getin_p('cloudth_sigma2s_power',sigma2s_power)
     483    CALL getin_p('cloudth_vert_alpha',vert_alpha)
     484    vert_alpha_th=vert_alpha
     485    CALL getin_p('cloudth_vert_alpha_th',vert_alpha_th)
     486    CALL getin_p('iflag_cloudth_vert_noratqs',iflag_cloudth_vert_noratqs)
    431487
    432488    WRITE(lunout,*) 'lscp_ini, niter_lscp:', niter_lscp
     
    439495    WRITE(lunout,*) 'lscp_ini, iflag_vice:', iflag_vice
    440496    WRITE(lunout,*) 'lscp_ini, iflag_t_glace:', iflag_t_glace
    441     WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
    442497    WRITE(lunout,*) 'lscp_ini, iflag_gammasat:', iflag_gammasat
    443498    WRITE(lunout,*) 'lscp_ini, iflag_rain_incloud_vol:', iflag_rain_incloud_vol
     
    467522    WRITE(lunout,*) 'lscp_ini, naero5', naero5
    468523    WRITE(lunout,*) 'lscp_ini, gamma_snwretro', gamma_snwretro
     524    WRITE(lunout,*) 'lscp_ini, gamma_mixth', gamma_mixth
    469525    WRITE(lunout,*) 'lscp_ini, gamma_taud', gamma_taud
    470526    WRITE(lunout,*) 'lscp_ini, iflag_oldbug_fisrtilp', iflag_oldbug_fisrtilp
     
    475531    WRITE(lunout,*) 'lscp_ini, ok_poprecip', ok_poprecip
    476532    WRITE(lunout,*) 'lscp_ini, ok_corr_vap_evasub', ok_corr_vap_evasub
     533    WRITE(lunout,*) 'lscp_ini, ok_growth_precip_deposition', ok_growth_precip_deposition
    477534    WRITE(lunout,*) 'lscp_ini, rain_int_min:', rain_int_min
    478535    WRITE(lunout,*) 'lscp_ini, gamma_agg:', gamma_agg
     
    483540    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_max:',tau_auto_snow_max
    484541    WRITE(lunout,*) 'lscp_ini, tau_auto_snow_min:',tau_auto_snow_min
     542    WRITE(lunout,*) 'lscp_ini, expo_tau_auto_snow:',expo_tau_auto_snow
    485543    WRITE(lunout,*) 'lscp_ini, r_snow:', r_snow
     544    WRITE(lunout,*) 'lscp_ini, alpha_freez:', alpha_freez
     545    WRITE(lunout,*) 'lscp_ini, beta_freez:', beta_freez
    486546    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_clr:', rain_fallspeed_clr
    487547    WRITE(lunout,*) 'lscp_ini, rain_fallspeed_cld:', rain_fallspeed_cld
     
    508568    WRITE(lunout,*) 'lscp_ini, coef_shear_lscp:', coef_shear_lscp
    509569    WRITE(lunout,*) 'lscp_ini, chi_mixing_lscp:', chi_mixing_lscp
    510 
    511 
    512 
    513 
     570    ! for cloudth routines
     571    WRITE(lunout,*) 'lscp_ini, ok_lscp_mergecond:', ok_lscp_mergecond
     572    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert:', iflag_cloudth_vert
     573    WRITE(lunout,*) 'lscp_ini, cloudth_ratqsmin:', cloudth_ratqsmin
     574    WRITE(lunout,*) 'lscp_ini, cloudth_sigma1s_factor:', sigma1s_factor
     575    WRITE(lunout,*) 'lscp_ini, cloudth_sigma1s_power:', sigma1s_power
     576    WRITE(lunout,*) 'lscp_ini, cloudth_sigma2s_factor:', sigma2s_factor
     577    WRITE(lunout,*) 'lscp_ini, cloudth_sigma2s_power:', sigma2s_power
     578    WRITE(lunout,*) 'lscp_ini, cloudth_vert_alpha:', vert_alpha
     579    WRITE(lunout,*) 'lscp_ini, cloudth_vert_alpha_th:', vert_alpha_th
     580    WRITE(lunout,*) 'lscp_ini, iflag_cloudth_vert_noratqs:', iflag_cloudth_vert_noratqs
     581
     582
     583    ! check consistency for cloud phase partitioning options
     584
     585    IF ((iflag_icefrac .GE. 2) .AND. (.NOT. ok_lscp_mergecond)) THEN
     586      abort_message = 'in lscp, iflag_icefrac .GE. 2 works only if ok_lscp_mergecond=.TRUE.'
     587      CALL abort_physic (modname,abort_message,1)
     588    ENDIF
    514589
    515590    ! check for precipitation sub-time steps
     
    522597    ! and other options
    523598   
    524     IF (iflag_autoconversion .EQ. 2) THEN
     599    IF ((iflag_autoconversion .EQ. 2) .AND. .NOT. ok_poprecip) THEN
    525600        IF ((iflag_vice .NE. 0) .OR. (niter_lscp .GT. 1)) THEN
    526601           abort_message = 'in lscp, iflag_autoconversion=2 requires iflag_vice=0 and niter_lscp=1'
     
    539614      CALL abort_physic (modname,abort_message,1)
    540615    ENDIF
     616
     617    IF ( (iflag_icefrac .GE. 1) .AND. (.NOT. ok_poprecip .AND. (iflag_evap_prec .LT. 4)) ) THEN
     618      abort_message = 'in lscp, icefracturb works with poprecip or with precip evap option >=4'
     619      CALL abort_physic (modname,abort_message,1)
     620    ENDIF
     621
    541622
    542623
     
    547628    a_tr_sca(4) = -0.5
    548629   
    549     CALL cloudth_ini(iflag_cloudth_vert,iflag_ratqs)
    550630
    551631RETURN
Note: See TracChangeset for help on using the changeset viewer.