Changeset 5614 for LMDZ6/trunk/libf/phylmd/lmdz_lscp_precip.f90
- Timestamp:
- Apr 14, 2025, 9:21:07 PM (8 weeks ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/lmdz_lscp_precip.f90
r5430 r5614 330 330 LOGICAL, INTENT(IN) :: iftop !--if top of the column 331 331 332 332 333 REAL, INTENT(IN), DIMENSION(klon) :: paprsdn !--pressure at the bottom interface of the layer [Pa] 333 334 REAL, INTENT(IN), DIMENSION(klon) :: paprsup !--pressure at the top interface of the layer [Pa] … … 540 541 IF (zoliqi(i) .GT. 0.) THEN 541 542 zfroi=(zoliqi(i)-((zoliqi(i)**(-dice_velo)) & 542 +dice_velo*dtime/REAL(niter_lscp)*cice_velo/zdz(i) *ffallv)**(-1./dice_velo))543 +dice_velo*dtime/REAL(niter_lscp)*cice_velo/zdz(i)/zneb(i)*zrho(i)*ffallv)**(-1./dice_velo)) 543 544 ELSE 544 545 zfroi=0. … … 618 619 ! Computation of DT if all the liquid precip freezes 619 620 DeltaT = RLMLT*zqprecl(i) / (zcp*(1.+coef1)) 621 622 620 623 ! T should not exceed the freezing point 621 624 ! that is Delta > RTT-zt(i) … … 722 725 USE lmdz_lscp_ini, ONLY : RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG 723 726 USE lmdz_lscp_ini, ONLY : ok_corr_vap_evasub, ok_ice_supersat, ok_unadjusted_clouds 724 USE lmdz_lscp_ini, ONLY : eps, temp_nowater 727 USE lmdz_lscp_ini, ONLY : eps, temp_nowater, ok_growth_precip_deposition 725 728 USE lmdz_lscp_tools, ONLY : calc_qsat_ecmwf 726 729 … … 792 795 dqreva(:) = 0. 793 796 dqssub(:) = 0. 794 dqrevap = 0.795 dqssubl = 0.796 797 797 798 !-- dhum_to_dflux = rho * dz/dt = 1 / g * dP/dt … … 880 881 DO i = 1, klon 881 882 883 dqrevap = 0. 884 dqssubl = 0. 882 885 !--If there is precipitation from the layer above 883 886 IF ( ( rain(i) + snow(i) ) .GT. 0. ) THEN … … 913 916 IF ( ( 1. - precipfraccld(i) ) .GT. eps ) THEN 914 917 qvapclr = qvapclrup(i) / qtotupnew(i) * qvap(i) / ( 1. - precipfraccld(i) ) 918 ELSE 919 qvapclr = 0. 920 ENDIF 921 IF ( precipfraccld(i) .GT. eps ) THEN 922 qvapcld = MAX(qtotupnew(i)-qvapclrup(i) , 0.) / qtotupnew(i) * qvap(i) / precipfraccld(i) 923 ELSE 924 qvapcld = 0. 915 925 ENDIF 916 926 ELSE … … 918 928 !--for the evap / subl process 919 929 qvapclr = qvap(i) 930 qvapcld = qvap(i) 920 931 ENDIF 921 932 … … 940 951 !--NB. with ok_ice_supersat activated, this barrier should be useless 941 952 drainclreva = MIN(0., drainclreva) 942 953 954 ! we set it to 0 as not sufficiently tested 955 drainclreva = 0. 943 956 944 957 !--Sublimation of the solid precipitation coming from above … … 986 999 ENDIF 987 1000 1001 ELSE 1002 1003 !--All the precipitation is sublimated if the fraction is zero 1004 drainclreva = - rainclr_tmp(i) 1005 dsnowclrsub = - snowclr_tmp(i) 1006 988 1007 ENDIF ! precipfracclr_tmp .GT. eps 989 1008 … … 993 1012 !--------------------------- 994 1013 995 IF ( ok_ unadjusted_clouds .AND. ( temp(i) .LE. temp_nowater) .AND. ( precipfraccld_tmp(i) .GT. eps ) ) THEN1014 IF ( ok_growth_precip_deposition .AND. ( temp(i) .LE. RTT ) .AND. ( precipfraccld_tmp(i) .GT. eps ) ) THEN 996 1015 !--Evaporation of liquid precipitation coming from above 997 1016 !--in the cloud only … … 1000 1019 !--Exact explicit formulation (raincld is resolved exactly, qvap explicitly) 1001 1020 !--which does not need a barrier on raincld, because included in the formula 1002 !draincldeva = precipfraccld_tmp(i) * MAX(0., & 1003 ! - coef_eva * ( 1. - expo_eva ) * (1. - qvapcld / qsatl(i)) * dz(i) & 1004 ! + ( raincld_tmp(i) / precipfraccld_tmp(i) )**( 1. - expo_eva ) & 1005 ! )**( 1. / ( 1. - expo_eva ) ) - raincld_tmp(i) 1006 1021 1022 draincldeva = precipfraccld_tmp(i) * MAX(0., & 1023 - coef_eva * ( 1. - expo_eva ) * (1. - qvapcld / qsatl(i)) * dz(i) & 1024 + ( raincld_tmp(i) / precipfraccld_tmp(i) )**( 1. - expo_eva ) & 1025 )**( 1. / ( 1. - expo_eva ) ) - raincld_tmp(i) 1026 1007 1027 !--Evaporation is limited by 0 1008 1028 !--NB. with ok_ice_supersat activated, this barrier should be useless 1009 !draincldeva = MIN(0., draincldeva) 1010 draincldeva = 0. 1029 draincldeva = MIN(0., draincldeva) 1011 1030 1012 1031 … … 1277 1296 1278 1297 USE lmdz_lscp_ini, ONLY : cld_lc_con, cld_tau_con, cld_expo_con, seuil_neb, & 1279 cld_lc_lsc, cld_tau_lsc, cld_expo_lsc, rain_int_min,&1298 cld_lc_lsc, cld_tau_lsc, cld_expo_lsc, & 1280 1299 thresh_precip_frac, gamma_col, gamma_agg, gamma_rim, & 1281 1300 rho_rain, r_rain, r_snow, rho_ice, & 1301 expo_tau_auto_snow, & 1282 1302 tau_auto_snow_min, tau_auto_snow_max, & 1283 thresh_precip_frac, eps, 1303 thresh_precip_frac, eps, rain_int_min, & 1284 1304 gamma_melt, alpha_freez, beta_freez, temp_nowater, & 1285 1305 iflag_cloudth_vert, iflag_rain_incloud_vol, & … … 1340 1360 REAL, DIMENSION(klon) :: dhum_to_dflux 1341 1361 REAL, DIMENSION(klon) :: qtot !--includes vap, liq, ice and precip 1362 REAL :: min_precip !--minimum precip flux below which precip fraction decreases 1342 1363 1343 1364 !--Collection, aggregation and riming … … 1502 1523 !--tau for snow depends on the ice fraction in mixed-phase clouds 1503 1524 tau_auto_snow = tau_auto_snow_max & 1504 + ( tau_auto_snow_min - tau_auto_snow_max ) * ( 1. - icefrac(i))1525 + ( tau_auto_snow_min - tau_auto_snow_max ) * ((1. - icefrac(i))**expo_tau_auto_snow) 1505 1526 1506 1527 expo_auto_rain = cld_expo_con … … 1513 1534 !--tau for snow depends on the ice fraction in mixed-phase clouds 1514 1535 tau_auto_snow = tau_auto_snow_max & 1515 + ( tau_auto_snow_min - tau_auto_snow_max ) * ( 1. - icefrac(i))1536 + ( tau_auto_snow_min - tau_auto_snow_max ) * ((1. - icefrac(i))**expo_tau_auto_snow) 1516 1537 1517 1538 expo_auto_rain = cld_expo_lsc … … 1534 1555 - ( qice(i) / eff_cldfra / qthresh_auto_snow ) ** expo_auto_snow ) ) ) ) 1535 1556 1536 1537 1557 !--Barriers so that we don't create more rain/snow 1538 1558 !--than there is liquid/ice … … 1543 1563 qliq(i) = qliq(i) + dqlauto 1544 1564 qice(i) = qice(i) + dqiauto 1565 1545 1566 raincld(i) = raincld(i) - dqlauto * dhum_to_dflux(i) 1546 1567 snowcld(i) = snowcld(i) - dqiauto * dhum_to_dflux(i) … … 1710 1731 !--second: immersion freezing following (inspired by Bigg 1953) 1711 1732 !--the latter is parameterized as an exponential decrease of the rain 1712 !--water content with a homemade formul ya1733 !--water content with a homemade formula 1713 1734 !--This is based on a caracteritic time of freezing, which 1714 1735 !--exponentially depends on temperature so that it is … … 1717 1738 !--NB.: this process needs a temperature adjustment 1718 1739 !--dqrfreez_max : maximum rain freezing so that temperature 1719 !-- stays lower than 273 K [kg/kg]1740 !-- stays lower than 273 K [kg/kg] 1720 1741 !--tau_freez : caracteristic time of freezing [s] 1721 1742 !--gamma_freez : tuning parameter [s-1] … … 1798 1819 * EXP( - alpha_freez * ( temp(i) - temp_nowater ) / ( RTT - temp_nowater ) ) ) 1799 1820 1800 1801 1821 !--In clear air 1802 1822 IF ( rainclr(i) .GT. 0. ) THEN … … 1827 1847 !--Add tendencies 1828 1848 !--The MAX is needed because in some cases, the flux can be slightly negative (numerical precision) 1849 1829 1850 rainclr(i) = MAX(0., rainclr(i) + dqrclrfreez * dhum_to_dflux(i)) 1830 1851 raincld(i) = MAX(0., raincld(i) + dqrcldfreez * dhum_to_dflux(i)) … … 1833 1854 1834 1855 1856 1835 1857 !--Temperature adjustment with the uptake of latent 1836 1858 !--heat because of freezing 1859 1837 1860 temp(i) = temp(i) - dqrtotfreez_step2 * RLMLT / RCPD & 1838 1861 / ( 1. + RVTMP2 * qtot(i) ) 1839 1840 1862 !--Diagnostic tendencies 1841 1863 dqrtotfreez = dqrtotfreez_step1 + dqrtotfreez_step2 … … 1847 1869 1848 1870 1849 !--If the local flux of rain+snow in clear/cloudy air is lower than rain_int_min, 1850 !--we reduce the precipiration fraction in the clear/cloudy air so that the new 1851 !--local flux of rain+snow is equal to rain_int_min. 1871 !--If the local flux of rain+snow in clear air is lower than min_precip, 1872 !--we reduce the precipiration fraction in the clear air so that the new 1873 !--local flux of rain+snow is equal to min_precip. 1874 !--we apply the minimum only on the clear-sky fraction because the cloudy precip fraction 1875 !--already decreases out of clouds 1852 1876 !--Here, rain+snow is the gridbox-mean flux of precip. 1853 1877 !--Therefore, (rain+snow)/precipfrac is the local flux of precip. 1854 !--If the local flux of precip is lower than rain_int_min, i.e.,1855 !-- (rain+snow)/precipfrac < rain_int_min, i.e.,1856 !-- (rain+snow)/ rain_int_min< precipfrac , then we want to reduce1857 !--the precip fraction to the equality, i.e., precipfrac = (rain+snow)/ rain_int_min.1878 !--If the local flux of precip is lower than min_precip, i.e., 1879 !-- (rain+snow)/precipfrac < min_precip , i.e., 1880 !-- (rain+snow)/min_precip < precipfrac , then we want to reduce 1881 !--the precip fraction to the equality, i.e., precipfrac = (rain+snow)/min_precip. 1858 1882 !--Note that this is physically different than what is proposed in LTP thesis. 1859 precipfracclr(i) = MIN( precipfracclr(i), ( rainclr(i) + snowclr(i) ) / rain_int_min ) 1860 precipfraccld(i) = MIN( precipfraccld(i), ( raincld(i) + snowcld(i) ) / rain_int_min ) 1883 !--min_precip is either equal to rain_int_min or calculated as a very small fraction 1884 !--of the minimum precip flux estimated as the flux associated with the 1885 !--autoconversion threshold mass content 1886 !min_precip=1.e-6*(pplay(i)/RD/temp(i))*MIN(rain_fallspeed_clr*cld_lc_lsc,snow_fallspeed_clr*cld_lc_lsc_snow) 1887 min_precip=rain_int_min 1888 precipfracclr(i) = MIN( precipfracclr(i), ( rainclr(i) + snowclr(i) ) / min_precip ) 1861 1889 1862 1890 !--Calculate outputs
Note: See TracChangeset
for help on using the changeset viewer.