Ignore:
Timestamp:
Dec 19, 2024, 3:46:10 PM (11 hours ago)
Author:
aborella
Message:

Merge with trunk

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_precip.f90

    r5413 r5431  
    714714           klon, dtime, iftop, paprsdn, paprsup, pplay, temp, tempupnew, qvap, &
    715715           qprecip, precipfracclr, precipfraccld, qvapclrup, qtotupnew, &
     716           cldfra, rvc_seri, qliq, qice, &
    716717           rain, rainclr, raincld, snow, snowclr, snowcld, dqreva, dqssub &
    717718           )
     
    720721USE lmdz_lscp_ini, ONLY : coef_eva, coef_sub, expo_eva, expo_sub, thresh_precip_frac
    721722USE lmdz_lscp_ini, ONLY : RCPD, RLSTT, RLVTT, RLMLT, RVTMP2, RTT, RD, RG
    722 USE lmdz_lscp_ini, ONLY : ok_corr_vap_evasub
     723USE lmdz_lscp_ini, ONLY : ok_corr_vap_evasub, ok_ice_supersat, ok_unadjusted_clouds
     724USE lmdz_lscp_ini, ONLY : eps, temp_nowater
    723725USE lmdz_lscp_tools, ONLY : calc_qsat_ecmwf
    724726
     
    747749REAL,    INTENT(IN),    DIMENSION(klon) :: qtotupnew      !--total specific humidity IN THE LAYER ABOVE [kg/kg]
    748750
     751REAL,    INTENT(IN),    DIMENSION(klon) :: cldfra         !--cloud fraction at the beginning of lscp - used only if the cloud properties are advected [-]
     752REAL,    INTENT(IN),    DIMENSION(klon) :: rvc_seri       !--cloud water vapor at the beginning of lscp (ratio wrt total water) - used only if the cloud properties are advected [kg/kg]
     753REAL,    INTENT(IN),    DIMENSION(klon) :: qliq           !--liquid water content at the beginning of lscp - used only if the cloud properties are advected [kg/kg]
     754REAL,    INTENT(IN),    DIMENSION(klon) :: qice           !--ice water content at the beginning of lscp - used only if the cloud properties are advected [kg/kg]
     755
     756
    749757REAL,    INTENT(INOUT), DIMENSION(klon) :: rain           !--flux of rain gridbox-mean coming from the layer above [kg/s/m2]
    750758REAL,    INTENT(INOUT), DIMENSION(klon) :: rainclr        !--flux of rain gridbox-mean in clear sky coming from the layer above [kg/s/m2]
    751 REAL,    INTENT(IN),    DIMENSION(klon) :: raincld        !--flux of rain gridbox-mean in cloudy air coming from the layer above [kg/s/m2]
     759REAL,    INTENT(INOUT), DIMENSION(klon) :: raincld        !--flux of rain gridbox-mean in cloudy air coming from the layer above [kg/s/m2]
    752760REAL,    INTENT(INOUT), DIMENSION(klon) :: snow           !--flux of snow gridbox-mean coming from the layer above [kg/s/m2]
    753761REAL,    INTENT(INOUT), DIMENSION(klon) :: snowclr        !--flux of snow gridbox-mean in clear sky coming from the layer above [kg/s/m2]
    754 REAL,    INTENT(IN),    DIMENSION(klon) :: snowcld        !--flux of snow gridbox-mean in cloudy air coming from the layer above [kg/s/m2]
     762REAL,    INTENT(INOUT), DIMENSION(klon) :: snowcld        !--flux of snow gridbox-mean in cloudy air coming from the layer above [kg/s/m2]
    755763
    756764REAL,    INTENT(OUT),   DIMENSION(klon) :: dqreva         !--rain tendency due to evaporation [kg/kg/s]
     
    762770!--dhum_to_dflux: coef to convert a specific quantity variation to a flux variation
    763771REAL, DIMENSION(klon) :: dhum_to_dflux
    764 !--
     772!--Air density [kg/m3] and layer thickness [m]
    765773REAL, DIMENSION(klon) :: rho, dz
     774!--Temporary precip fractions and fluxes for the evaporation
     775REAL, DIMENSION(klon) :: precipfracclr_tmp, precipfraccld_tmp
     776REAL, DIMENSION(klon) :: rainclr_tmp, raincld_tmp, snowclr_tmp, snowcld_tmp
    766777
    767778!--Saturation values
    768779REAL, DIMENSION(klon) :: qzero, qsat, dqsat, qsatl, dqsatl, qsati, dqsati
    769 !--Vapor in the clear sky
    770 REAL :: qvapclr
     780!--Vapor in the clear sky and cloud
     781REAL :: qvapclr, qvapcld
    771782!--Fluxes tendencies because of evaporation and sublimation
    772 REAL :: dprecip_evasub_max, draineva, dsnowsub, dprecip_evasub_tot
     783REAL :: dprecip_evasub_max, dprecip_evasub_tot
     784REAL :: drainclreva, draincldeva, dsnowclrsub, dsnowcldsub
    773785!--Specific humidity tendencies because of evaporation and sublimation
    774786REAL :: dqrevap, dqssubl
     
    828840ENDIF
    829841
    830 ! TODO Probleme : on utilise qvap total dans la maille pour l'evap / sub
    831 ! alors qu'on n'evap / sub que dans le ciel clair
    832 ! deux options pour cette routine :
    833 ! - soit on diagnostique le nuage AVANT l'evap / sub et on estime donc
    834 ! la fraction precipitante ciel clair dans la maille, ce qui permet de travailler
    835 ! avec des fractions, des fluxs et surtout un qvap dans le ciel clair
    836 ! - soit on pousse la param de Ludo au bout, et on prend un qvap de k+1
    837 ! dans le ciel clair, avec un truc comme :
    838 !   qvapclr(k) = qvapclr(k+1)/qtot(k+1) * qtot(k)
    839 ! UPDATE : on code la seconde version. A voir si on veut mettre la premiere version.
    840 
    841 
     842
     843!--Initialise the precipitation fractions and fluxes
    842844DO i = 1, klon
     845  precipfracclr_tmp(i) = precipfracclr(i)
     846  precipfraccld_tmp(i) = precipfraccld(i)
     847  rainclr_tmp(i) = rainclr(i)
     848  snowclr_tmp(i) = snowclr(i)
     849  raincld_tmp(i) = raincld(i)
     850  snowcld_tmp(i) = snowcld(i)
     851ENDDO
     852
     853!--If we relax the LTP assumption that the cloud is the same than in the
     854!--gridbox above, we can change the tmp quantities
     855IF ( ok_ice_supersat ) THEN
     856  !--Update the precipitation fraction using advected cloud fraction
     857  CALL poprecip_fracupdate( &
     858             klon, cldfra, precipfracclr_tmp, precipfraccld_tmp, &
     859             rainclr_tmp, raincld_tmp, snowclr_tmp, snowcld_tmp)
     860
     861! here we could put an ELSE statement and do one iteration of the condensation scheme
     862! (but it would only diagnose cloud from lognormal - link with thermals?)
     863
     864  DO i = 1, klon
     865    !--We cannot have a total fraction greater than the one in the gridbox above
     866    !--because new cloud formation has not yet occured.
     867    !--If this happens, we reduce the precip frac in the cloud, because it can
     868    !--only mean that the cloud fraction at this level is greater than the total
     869    !--precipitation fraction of the level above, and the precip frac in clear sky
     870    !--is zero.
     871    !--NB. this only works because we assume a max-random cloud and precip overlap
     872    precipfraccld_tmp(i) = MIN( precipfraccld_tmp(i), precipfracclr(i) + precipfraccld(i) )
     873  ENDDO
     874
     875ENDIF
     876!--At this stage, we guarantee that
     877!-- precipfracclr + precipfraccld = precipfracclr_tmp + precipfraccld_tmp
     878
     879
     880DO i = 1, klon
    843881
    844882  !--If there is precipitation from the layer above
    845   ! NOTE TODO here we could replace the condition on precipfracclr(i) by a condition
    846   ! such as eps or thresh_precip_frac, to remove the senseless barrier in the formulas
    847   ! of evap / sublim
    848   IF ( ( ( rain(i) + snow(i) ) .GT. 0. ) .AND. ( precipfracclr(i) .GT. 0. ) ) THEN
    849 
    850     IF ( ok_corr_vap_evasub ) THEN
    851       !--Corrected version - we use the same water ratio between
     883  IF ( ( rain(i) + snow(i) ) .GT. 0. ) THEN
     884
     885    !--Init
     886    drainclreva = 0.
     887    draincldeva = 0.
     888    dsnowclrsub = 0.
     889    dsnowcldsub = 0.
     890
     891    !--Init the properties of the air where reevaporation occurs
     892    IF ( ok_ice_supersat ) THEN
     893      !--We can diagnose the water vapor in the cloud using the advected
     894      !--water vapor in the cloud and cloud fraction
     895      IF ( ok_unadjusted_clouds .AND. ( cldfra(i) .GT. eps ) ) THEN
     896        qvapcld = rvc_seri(i) * qvap(i) / cldfra(i)
     897      ENDIF
     898      !--We can diagnose completely the water vapor in clear sky, because all
     899      !--the needed variables (ice, liq, vapor in cld, cloud fraction) are
     900      !--advected
     901      !--Note that qvap(i) is the total water in the gridbox
     902      IF ( ( 1. - cldfra(i) ) .GT. eps ) THEN
     903        qvapclr = ( qvap(i) - qice(i) - qliq(i) - rvc_seri(i) * qvap(i) ) / ( 1. - cldfra(i) )
     904      ENDIF
     905    ELSEIF ( ok_corr_vap_evasub ) THEN
     906      !--Corrected version from Ludo - we use the same water ratio between
    852907      !--the clear and the cloudy sky as in the layer above. This
    853908      !--extends the assumption that the cloud fraction is the same
     
    856911      !--Note that qvap(i) is the total water in the gridbox, and
    857912      !--precipfraccld(i) is the cloud fraction in the layer above
    858       qvapclr = qvapclrup(i) / qtotupnew(i) * qvap(i) / ( 1. - precipfraccld(i) )
     913      IF ( ( 1. - precipfraccld(i) ) .GT. eps ) THEN
     914        qvapclr = qvapclrup(i) / qtotupnew(i) * qvap(i) / ( 1. - precipfraccld(i) )
     915      ENDIF
    859916    ELSE
    860917      !--Legacy version from Ludo - we use the total specific humidity
     
    863920    ENDIF
    864921
    865     !--Evaporation of liquid precipitation coming from above
    866     !--in the clear sky only
    867     !--dprecip/dz = -beta*(1-qvap/qsat)*(precip**expo_eva)
    868     !--formula from Sundqvist 1988, Klemp & Wilhemson 1978
    869     !--Exact explicit formulation (rainclr is resolved exactly, qvap explicitly)
    870     !--which does not need a barrier on rainclr, because included in the formula
    871     draineva = precipfracclr(i) * ( MAX(0., &
    872              - coef_eva * ( 1. - expo_eva ) * (1. - qvapclr / qsatl(i)) * dz(i) &
    873              + ( rainclr(i) / MAX(thresh_precip_frac, precipfracclr(i)) )**( 1. - expo_eva ) &
    874                ) )**( 1. / ( 1. - expo_eva ) ) - rainclr(i)
    875              
    876     !--Evaporation is limited by 0
    877     draineva = MIN(0., draineva)
    878 
    879 
    880     !--Sublimation of the solid precipitation coming from above
    881     !--(same formula as for liquid precip)
    882     !--Exact explicit formulation (snowclr is resolved exactly, qvap explicitly)
    883     !--which does not need a barrier on snowclr, because included in the formula
    884     dsnowsub = precipfracclr(i) * ( MAX(0., &
    885              - coef_sub * ( 1. - expo_sub ) * (1. - qvapclr / qsati(i)) * dz(i) &
    886              + ( snowclr(i) / MAX(thresh_precip_frac, precipfracclr(i)) )**( 1. - expo_sub ) &
    887              ) )**( 1. / ( 1. - expo_sub ) ) - snowclr(i)
    888 
    889     !--Sublimation is limited by 0
    890     ! TODO: change max when we will allow for vapor deposition in supersaturated regions
    891     dsnowsub = MIN(0., dsnowsub)
    892 
    893     !--Evaporation limit: we ensure that the layer's fraction below
    894     !--the clear sky does not reach saturation. In this case, we
    895     !--redistribute the maximum flux dprecip_evasub_max conserving the ratio liquid/ice
    896     !--Max evaporation is computed not to saturate the clear sky precip fraction
    897     !--(i.e., the fraction where evaporation occurs)
    898     !--It is expressed as a max flux dprecip_evasub_max
    899    
    900     dprecip_evasub_max = MIN(0., ( qvapclr - qsat(i) ) * precipfracclr(i)) &
    901                      * dhum_to_dflux(i)
    902     dprecip_evasub_tot = draineva + dsnowsub
    903 
    904     !--Barriers
    905     !--If activates if the total is LOWER than the max because
    906     !--everything is negative
    907     IF ( dprecip_evasub_tot .LT. dprecip_evasub_max ) THEN
    908       draineva = dprecip_evasub_max * draineva / dprecip_evasub_tot
    909       dsnowsub = dprecip_evasub_max * dsnowsub / dprecip_evasub_tot
    910     ENDIF
     922    !---------------------------
     923    !-- EVAP / SUBL IN CLEAR SKY
     924    !---------------------------
     925
     926    IF ( precipfracclr_tmp(i) .GT. eps ) THEN
     927
     928      !--Evaporation of liquid precipitation coming from above
     929      !--in the clear sky only
     930      !--dprecip/dz = -beta*(1-qvap/qsat)*(precip**expo_eva)
     931      !--formula from Sundqvist 1988, Klemp & Wilhemson 1978
     932      !--Exact explicit formulation (rainclr is resolved exactly, qvap explicitly)
     933      !--which does not need a barrier on rainclr, because included in the formula
     934      drainclreva = precipfracclr_tmp(i) * MAX(0., &
     935                  - coef_eva * ( 1. - expo_eva ) * (1. - qvapclr / qsatl(i)) * dz(i) &
     936                  + ( rainclr_tmp(i) / precipfracclr_tmp(i) )**( 1. - expo_eva ) &
     937                  )**( 1. / ( 1. - expo_eva ) ) - rainclr_tmp(i)
     938               
     939      !--Evaporation is limited by 0
     940      !--NB. with ok_ice_supersat activated, this barrier should be useless
     941      drainclreva = MIN(0., drainclreva)
     942
     943
     944      !--Sublimation of the solid precipitation coming from above
     945      !--(same formula as for liquid precip)
     946      !--Exact explicit formulation (snowclr is resolved exactly, qvap explicitly)
     947      !--which does not need a barrier on snowclr, because included in the formula
     948      dsnowclrsub = precipfracclr_tmp(i) * MAX(0., &
     949                  - coef_sub * ( 1. - expo_sub ) * (1. - qvapclr / qsati(i)) * dz(i) &
     950                  + ( snowclr_tmp(i) / precipfracclr_tmp(i) )**( 1. - expo_sub ) &
     951                  )**( 1. / ( 1. - expo_sub ) ) - snowclr_tmp(i)
     952
     953      !--If ice supersaturation is activated, we allow vapor to condense on falling snow
     954      !--i.e., having a positive dsnowclrsub
     955      IF ( .NOT. ok_ice_supersat ) THEN
     956        !--Sublimation is limited by 0
     957        dsnowclrsub = MIN(0., dsnowclrsub)
     958      ENDIF
     959
     960
     961      !--Evaporation limit: we ensure that the layer's fraction below
     962      !--the clear sky does not reach saturation. In this case, we
     963      !--redistribute the maximum flux dprecip_evasub_max conserving the ratio liquid/ice
     964      !--Max evaporation is computed not to saturate the clear sky precip fraction
     965      !--(i.e., the fraction where evaporation occurs)
     966      !--It is expressed as a max flux dprecip_evasub_max
     967     
     968      IF ( .NOT. ok_ice_supersat ) THEN
     969        dprecip_evasub_max = MIN(0., ( qvapclr - qsat(i) ) * precipfracclr_tmp(i)) &
     970                         * dhum_to_dflux(i)
     971      ELSE
     972        dprecip_evasub_max = ( qvapclr - qsat(i) ) * precipfracclr_tmp(i) &
     973                         * dhum_to_dflux(i)
     974      ENDIF
     975      dprecip_evasub_tot = drainclreva + dsnowclrsub
     976
     977      !--Barriers
     978      !--If activates if the total is LOWER than the max because
     979      !--everything is negative
     980      IF ( (( dprecip_evasub_max .LT. 0. ) .AND. &
     981            ( dprecip_evasub_tot .LT. dprecip_evasub_max )) .OR. &
     982           (( dprecip_evasub_max .GT. 0. ) .AND. &
     983            ( dprecip_evasub_tot .GT. dprecip_evasub_max )) ) THEN
     984        drainclreva = dprecip_evasub_max * drainclreva / dprecip_evasub_tot
     985        dsnowclrsub = dprecip_evasub_max * dsnowclrsub / dprecip_evasub_tot
     986      ENDIF
     987
     988    ENDIF ! precipfracclr_tmp .GT. eps
     989
     990
     991    !---------------------------
     992    !-- EVAP / SUBL IN THE CLOUD
     993    !---------------------------
     994
     995    IF ( ok_unadjusted_clouds .AND. ( temp(i) .LE. temp_nowater ) .AND. ( precipfraccld_tmp(i) .GT. eps ) ) THEN
     996      !--Evaporation of liquid precipitation coming from above
     997      !--in the cloud only
     998      !--dprecip/dz = -beta*(1-qvap/qsat)*(precip**expo_eva)
     999      !--formula from Sundqvist 1988, Klemp & Wilhemson 1978
     1000      !--Exact explicit formulation (raincld is resolved exactly, qvap explicitly)
     1001      !--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               
     1007      !--Evaporation is limited by 0
     1008      !--NB. with ok_ice_supersat activated, this barrier should be useless
     1009      !draincldeva = MIN(0., draincldeva)
     1010      draincldeva = 0.
     1011
     1012
     1013      !--Sublimation of the solid precipitation coming from above
     1014      !--(same formula as for liquid precip)
     1015      !--Exact explicit formulation (snowcld is resolved exactly, qvap explicitly)
     1016      !--which does not need a barrier on snowcld, because included in the formula
     1017      dsnowcldsub = precipfraccld_tmp(i) * MAX(0., &
     1018                  - coef_sub * ( 1. - expo_sub ) * (1. - qvapcld / qsati(i)) * dz(i) &
     1019                  + ( snowcld_tmp(i) / precipfraccld_tmp(i) )**( 1. - expo_sub ) &
     1020                  )**( 1. / ( 1. - expo_sub ) ) - snowcld_tmp(i)
     1021
     1022      !--There is no barrier because we want deposition to occur if it is possible
     1023
     1024
     1025      !--Evaporation limit: we ensure that the layer's fraction below
     1026      !--the clear sky does not reach saturation. In this case, we
     1027      !--redistribute the maximum flux dprecip_evasub_max conserving the ratio liquid/ice
     1028      !--Max evaporation is computed not to saturate the clear sky precip fraction
     1029      !--(i.e., the fraction where evaporation occurs)
     1030      !--It is expressed as a max flux dprecip_evasub_max
     1031     
     1032      dprecip_evasub_max = ( qvapcld - qsat(i) ) * precipfraccld_tmp(i) * dhum_to_dflux(i)
     1033      dprecip_evasub_tot = draincldeva + dsnowcldsub
     1034
     1035      !--Barriers
     1036      !--If activates if the total is LOWER than the max because
     1037      !--everything is negative
     1038      IF ( (( dprecip_evasub_max .LT. 0. ) .AND. &
     1039            ( dprecip_evasub_tot .LT. dprecip_evasub_max )) .OR. &
     1040           (( dprecip_evasub_max .GT. 0. ) .AND. &
     1041            ( dprecip_evasub_tot .GT. dprecip_evasub_max )) ) THEN
     1042        draincldeva = dprecip_evasub_max * draincldeva / dprecip_evasub_tot
     1043        dsnowcldsub = dprecip_evasub_max * dsnowcldsub / dprecip_evasub_tot
     1044      ENDIF
     1045
     1046    ENDIF ! ok_unadjusted_clouds
    9111047
    9121048
    9131049    !--New solid and liquid precipitation fluxes after evap and sublimation
    914     dqrevap = draineva / dhum_to_dflux(i)
    915     dqssubl = dsnowsub / dhum_to_dflux(i)
    916 
     1050    dqrevap = ( drainclreva + draincldeva ) / dhum_to_dflux(i)
     1051    dqssubl = ( dsnowclrsub + dsnowcldsub ) / dhum_to_dflux(i)
    9171052
    9181053    !--Vapor is updated after evaporation/sublimation (it is increased)
     
    9291064
    9301065    !--Add tendencies
    931     !--The MAX is needed because in some cases, the flux can be slightly negative (numerical precision)
    932     rainclr(i) = MAX(0., rainclr(i) + draineva)
    933     snowclr(i) = MAX(0., snowclr(i) + dsnowsub)
    934 
    935     !--If there is no more precip fluxes, the precipitation fraction in clear
    936     !--sky is set to 0
     1066    !--The MAX is needed because in some cases, the flux can be slightly
     1067    !--negative (numerical precision)
     1068    rainclr_tmp(i) = MAX(0., rainclr_tmp(i) + drainclreva)
     1069    snowclr_tmp(i) = MAX(0., snowclr_tmp(i) + dsnowclrsub)
     1070    raincld_tmp(i) = MAX(0., raincld_tmp(i) + draincldeva)
     1071    snowcld_tmp(i) = MAX(0., snowcld_tmp(i) + dsnowcldsub)
     1072
     1073
     1074    !--We reattribute fluxes according to initial fractions, using proportionnality
     1075    !--Note that trough this process, we conserve total precip fluxes
     1076    !-- rainclr_tmp + raincld_tmp = rainclr + raincld (same for snow)
     1077    !--If the cloud has increased, a part of the precip in clear sky falls in clear sky,
     1078    !--the rest falls in the cloud
     1079    IF ( ( precipfraccld(i) .GT. eps ) .AND. ( precipfraccld_tmp(i) .GT. precipfraccld(i) ) ) THEN
     1080      !--All the precip from cloud falls in the cloud
     1081      raincld(i) = MAX(0., raincld_tmp(i) * precipfraccld(i) / precipfraccld_tmp(i))
     1082      rainclr(i) = MAX(0., rainclr_tmp(i) + raincld_tmp(i) - raincld(i))
     1083      snowcld(i) = MAX(0., snowcld_tmp(i) * precipfraccld(i) / precipfraccld_tmp(i))
     1084      snowclr(i) = MAX(0., snowclr_tmp(i) + snowcld_tmp(i) - snowcld(i))
     1085
     1086    !--If the cloud has narrowed, a part of the precip in cloud falls in clear sky,
     1087    !--the rest falls in the cloud
     1088    ELSEIF ( ( precipfracclr(i) .GT. eps ) .AND. ( precipfracclr_tmp(i) .GT. precipfracclr(i) ) ) THEN
     1089      !--All the precip from clear sky falls in clear sky
     1090      rainclr(i) = MAX(0., rainclr_tmp(i) * precipfracclr(i) / precipfracclr_tmp(i))
     1091      raincld(i) = MAX(0., raincld_tmp(i) + rainclr_tmp(i) - rainclr(i))
     1092      snowclr(i) = MAX(0., snowclr_tmp(i) * precipfracclr(i) / precipfracclr_tmp(i))
     1093      snowcld(i) = MAX(0., snowcld_tmp(i) + snowclr_tmp(i) - snowclr(i))
     1094
     1095    ELSE
     1096      !--If the cloud stays the same or if there is no cloud above and
     1097      !--in the current layer, there is no reattribution
     1098      rainclr(i) = rainclr_tmp(i)
     1099      raincld(i) = raincld_tmp(i)
     1100      snowclr(i) = snowclr_tmp(i)
     1101      snowcld(i) = snowcld_tmp(i)                                     
     1102    ENDIF
     1103
     1104    !--If there is no more precip fluxes, the precipitation fraction is set to 0
    9371105    IF ( ( rainclr(i) + snowclr(i) ) .LE. 0. ) precipfracclr(i) = 0.
     1106    IF ( ( raincld(i) + snowcld(i) ) .LE. 0. ) precipfraccld(i) = 0.
    9381107
    9391108    !--Calculation of the total fluxes
     
    9551124
    9561125END SUBROUTINE poprecip_precld
     1126
     1127
     1128!----------------------------------------------------------------
     1129! Computes the precipitation fraction update
     1130! The goal of this routine is to reattribute precipitation fractions
     1131! and fluxes to clear or cloudy air, depending on the variation of
     1132! the cloud fraction on the vertical dimension. We assume a
     1133! maximum-random overlap of the cloud cover (see Jakob and Klein, 2000,
     1134! and LTP thesis, 2021)
     1135! NB. in fact, we assume a maximum-random overlap of the total precip. frac
     1136!
     1137SUBROUTINE poprecip_fracupdate( &
     1138           klon, cldfra, precipfracclr, precipfraccld, &
     1139           rainclr, raincld, snowclr, snowcld)
     1140
     1141USE lmdz_lscp_ini, ONLY : eps
     1142
     1143IMPLICIT NONE
     1144
     1145INTEGER, INTENT(IN)                     :: klon           !--number of horizontal grid points [-]
     1146
     1147REAL,    INTENT(IN),    DIMENSION(klon) :: cldfra         !--cloud fraction [-]
     1148REAL,    INTENT(INOUT), DIMENSION(klon) :: precipfracclr  !--fraction of precipitation in the clear sky IN THE LAYER ABOVE [-]
     1149REAL,    INTENT(INOUT), DIMENSION(klon) :: precipfraccld  !--fraction of precipitation in the cloudy air IN THE LAYER ABOVE [-]
     1150                                                          !--NB. at the end of the routine, becomes the fraction of precip
     1151                                                          !--in the current layer
     1152
     1153REAL,    INTENT(INOUT), DIMENSION(klon) :: rainclr        !--flux of rain gridbox-mean in clear sky coming from the layer above [kg/s/m2]
     1154REAL,    INTENT(INOUT), DIMENSION(klon) :: raincld        !--flux of rain gridbox-mean in cloudy air coming from the layer above [kg/s/m2]
     1155REAL,    INTENT(INOUT), DIMENSION(klon) :: snowclr        !--flux of snow gridbox-mean in clear sky coming from the layer above [kg/s/m2]
     1156REAL,    INTENT(INOUT), DIMENSION(klon) :: snowcld        !--flux of snow gridbox-mean in cloudy air coming from the layer above [kg/s/m2]
     1157
     1158!--Local variables
     1159INTEGER :: i
     1160REAL :: dcldfra
     1161REAL :: precipfractot
     1162REAL :: dprecipfracclr, dprecipfraccld
     1163REAL :: drainclr, dsnowclr
     1164REAL :: draincld, dsnowcld
     1165
     1166
     1167DO i = 1, klon
     1168
     1169  !--Initialisation
     1170  precipfractot = precipfracclr(i) + precipfraccld(i)
     1171
     1172  !--Instead of using the cloud cover which was use in LTP thesis, we use the
     1173  !--total precip. fraction to compute the maximum-random overlap. This is
     1174  !--because all the information of the cloud cover is embedded into
     1175  !--precipfractot, and this allows for taking into account the potential
     1176  !--reduction of the precipitation fraction because either the flux is too
     1177  !--small (see barrier at the end of poprecip_postcld) or the flux is completely
     1178  !--evaporated (see barrier at the end of poprecip_precld)
     1179  !--NB. precipfraccld(i) is here the cloud fraction of the layer above
     1180  !precipfractot = 1. - ( 1. - precipfractot ) * &
     1181  !               ( 1. - MAX( cldfra(i), precipfraccld(i) ) ) &
     1182  !             / ( 1. - MIN( precipfraccld(i), 1. - eps ) )
     1183
     1184
     1185  IF ( precipfraccld(i) .GT. ( 1. - eps ) ) THEN
     1186    precipfractot = 1.
     1187  ELSE
     1188    precipfractot = 1. - ( 1. - precipfractot ) * &
     1189                 ( 1. - MAX( cldfra(i), precipfraccld(i) ) ) &
     1190               / ( 1. - precipfraccld(i) )
     1191  ENDIF
     1192
     1193  !--precipfraccld(i) is here the cloud fraction of the layer above
     1194  dcldfra = cldfra(i) - precipfraccld(i)
     1195  !--Tendency of the clear-sky precipitation fraction. We add a MAX on the
     1196  !--calculation of the current CS precip. frac.
     1197  !dprecipfracclr = MAX( 0., ( precipfractot - cldfra(i) ) ) - precipfracclr(i)
     1198  !--We remove it, because precipfractot is guaranteed to be > cldfra (the MAX is activated
     1199  !--if precipfractot < cldfra)
     1200  dprecipfracclr = ( precipfractot - cldfra(i) ) - precipfracclr(i)
     1201  !--Tendency of the cloudy precipitation fraction. We add a MAX on the
     1202  !--calculation of the current CS precip. frac.
     1203  !dprecipfraccld = MAX( dcldfra , - precipfraccld(i) )
     1204  !--We remove it, because cldfra is guaranteed to be > 0 (the MAX is activated
     1205  !--if cldfra < 0)
     1206  dprecipfraccld = dcldfra
     1207
     1208
     1209  !--If the cloud extends
     1210  IF ( dprecipfraccld .GT. 0. ) THEN
     1211    !--If there is no CS precip, nothing happens.
     1212    !--If there is, we reattribute some of the CS precip flux
     1213    !--to the cloud precip flux, proportionnally to the
     1214    !--decrease of the CS precip fraction
     1215    IF ( precipfracclr(i) .LT. eps ) THEN
     1216      drainclr = 0.
     1217      dsnowclr = 0.
     1218    ELSE
     1219      drainclr = dprecipfracclr / precipfracclr(i) * rainclr(i)
     1220      dsnowclr = dprecipfracclr / precipfracclr(i) * snowclr(i)
     1221    ENDIF
     1222  !--If the cloud narrows
     1223  ELSEIF ( dprecipfraccld .LT. 0. ) THEN
     1224    !--We reattribute some of the cloudy precip flux
     1225    !--to the CS precip flux, proportionnally to the
     1226    !--decrease of the cloud precip fraction
     1227    IF ( precipfraccld(i) .LT. eps ) THEN
     1228      draincld = 0.
     1229      dsnowcld = 0.
     1230    ELSE
     1231      draincld = dprecipfraccld / precipfraccld(i) * raincld(i)
     1232      dsnowcld = dprecipfraccld / precipfraccld(i) * snowcld(i)
     1233    ENDIF
     1234    drainclr = - draincld
     1235    dsnowclr = - dsnowcld
     1236  !--If the cloud stays the same or if there is no cloud above and
     1237  !--in the current layer, nothing happens
     1238  ELSE
     1239    drainclr = 0.
     1240    dsnowclr = 0.
     1241  ENDIF
     1242
     1243  !--We add the tendencies
     1244  !--The MAX is needed because in some cases, the flux can be slightly negative (numerical precision)
     1245  precipfraccld(i) = precipfraccld(i) + dprecipfraccld
     1246  precipfracclr(i) = precipfracclr(i) + dprecipfracclr
     1247  rainclr(i) = MAX(0., rainclr(i) + drainclr)
     1248  snowclr(i) = MAX(0., snowclr(i) + dsnowclr)
     1249  raincld(i) = MAX(0., raincld(i) - drainclr)
     1250  snowcld(i) = MAX(0., snowcld(i) - dsnowclr)
     1251
     1252ENDDO
     1253
     1254END SUBROUTINE poprecip_fracupdate
    9571255
    9581256
     
    10431341REAL, DIMENSION(klon) :: qtot                             !--includes vap, liq, ice and precip
    10441342
    1045 !--Partition of the fluxes
    1046 REAL :: dcldfra
    1047 REAL :: precipfractot
    1048 REAL :: dprecipfracclr, dprecipfraccld
    1049 REAL :: drainclr, dsnowclr
    1050 REAL :: draincld, dsnowcld
    1051 
    10521343!--Collection, aggregation and riming
    10531344REAL :: eff_cldfra
     
    10981389
    10991390
     1391!--Update the precipitation fraction following cloud formation
     1392CALL poprecip_fracupdate( &
     1393           klon, cldfra, precipfracclr, precipfraccld, &
     1394           rainclr, raincld, snowclr, snowcld)
     1395
     1396
    11001397DO i = 1, klon
    11011398
     
    11111408  qtot(i) = qvap(i) + qliq(i) + qice(i) &
    11121409          + ( raincld(i) + rainclr(i) + snowcld(i) + snowclr(i) ) / dhum_to_dflux(i)
    1113 
    1114   !------------------------------------------------------------
    1115   !--     PRECIPITATION FRACTIONS UPDATE
    1116   !------------------------------------------------------------
    1117   !--The goal of this routine is to reattribute precipitation fractions
    1118   !--and fluxes to clear or cloudy air, depending on the variation of
    1119   !--the cloud fraction on the vertical dimension. We assume a
    1120   !--maximum-random overlap of the cloud cover (see Jakob and Klein, 2000,
    1121   !--and LTP thesis, 2021)
    1122   !--NB. in fact, we assume a maximum-random overlap of the total precip. frac
    1123 
    1124   !--Initialisation
    1125   precipfractot = precipfracclr(i) + precipfraccld(i)
    1126 
    1127   !--Instead of using the cloud cover which was use in LTP thesis, we use the
    1128   !--total precip. fraction to compute the maximum-random overlap. This is
    1129   !--because all the information of the cloud cover is embedded into
    1130   !--precipfractot, and this allows for taking into account the potential
    1131   !--reduction of the precipitation fraction because either the flux is too
    1132   !--small (see barrier at the end of poprecip_postcld) or the flux is completely
    1133   !--evaporated (see barrier at the end of poprecip_precld)
    1134   !--NB. precipfraccld(i) is here the cloud fraction of the layer above
    1135   !precipfractot = 1. - ( 1. - precipfractot ) * &
    1136   !               ( 1. - MAX( cldfra(i), precipfraccld(i) ) ) &
    1137   !             / ( 1. - MIN( precipfraccld(i), 1. - eps ) )
    1138 
    1139 
    1140   IF ( precipfraccld(i) .GT. ( 1. - eps ) ) THEN
    1141     precipfractot = 1.
    1142   ELSE
    1143     precipfractot = 1. - ( 1. - precipfractot ) * &
    1144                  ( 1. - MAX( cldfra(i), precipfraccld(i) ) ) &
    1145                / ( 1. - precipfraccld(i) )
    1146   ENDIF
    1147 
    1148   !--precipfraccld(i) is here the cloud fraction of the layer above
    1149   dcldfra = cldfra(i) - precipfraccld(i)
    1150   !--Tendency of the clear-sky precipitation fraction. We add a MAX on the
    1151   !--calculation of the current CS precip. frac.
    1152   !dprecipfracclr = MAX( 0., ( precipfractot - cldfra(i) ) ) - precipfracclr(i)
    1153   !--We remove it, because precipfractot is guaranteed to be > cldfra (the MAX is activated
    1154   !--if precipfractot < cldfra)
    1155   dprecipfracclr = ( precipfractot - cldfra(i) ) - precipfracclr(i)
    1156   !--Tendency of the cloudy precipitation fraction. We add a MAX on the
    1157   !--calculation of the current CS precip. frac.
    1158   !dprecipfraccld = MAX( dcldfra , - precipfraccld(i) )
    1159   !--We remove it, because cldfra is guaranteed to be > 0 (the MAX is activated
    1160   !--if cldfra < 0)
    1161   dprecipfraccld = dcldfra
    1162 
    1163 
    1164   !--If the cloud extends
    1165   IF ( dprecipfraccld .GT. 0. ) THEN
    1166     !--If there is no CS precip, nothing happens.
    1167     !--If there is, we reattribute some of the CS precip flux
    1168     !--to the cloud precip flux, proportionnally to the
    1169     !--decrease of the CS precip fraction
    1170     IF ( precipfracclr(i) .LE. 0. ) THEN
    1171       drainclr = 0.
    1172       dsnowclr = 0.
    1173     ELSE
    1174       drainclr = dprecipfracclr / precipfracclr(i) * rainclr(i)
    1175       dsnowclr = dprecipfracclr / precipfracclr(i) * snowclr(i)
    1176     ENDIF
    1177   !--If the cloud narrows
    1178   ELSEIF ( dprecipfraccld .LT. 0. ) THEN
    1179     !--We reattribute some of the cloudy precip flux
    1180     !--to the CS precip flux, proportionnally to the
    1181     !--decrease of the cloud precip fraction
    1182     draincld = dprecipfraccld / precipfraccld(i) * raincld(i)
    1183     dsnowcld = dprecipfraccld / precipfraccld(i) * snowcld(i)
    1184     drainclr = - draincld
    1185     dsnowclr = - dsnowcld
    1186   !--If the cloud stays the same or if there is no cloud above and
    1187   !--in the current layer, nothing happens
    1188   ELSE
    1189     drainclr = 0.
    1190     dsnowclr = 0.
    1191   ENDIF
    1192 
    1193   !--We add the tendencies
    1194   !--The MAX is needed because in some cases, the flux can be slightly negative (numerical precision)
    1195   precipfraccld(i) = precipfraccld(i) + dprecipfraccld
    1196   precipfracclr(i) = precipfracclr(i) + dprecipfracclr
    1197   rainclr(i) = MAX(0., rainclr(i) + drainclr)
    1198   snowclr(i) = MAX(0., snowclr(i) + dsnowclr)
    1199   raincld(i) = MAX(0., raincld(i) - drainclr)
    1200   snowcld(i) = MAX(0., snowcld(i) - dsnowclr)
    12011410 
    12021411  !--If vertical heterogeneity is taken into account, we use
Note: See TracChangeset for help on using the changeset viewer.