Ignore:
Timestamp:
Jul 28, 2025, 6:44:28 PM (19 hours ago)
Author:
aborella
Message:

Major modifs to treatment of contrails (from 2 classes to 2 moments) + diagnostics. Increased numerical efficiency

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_precip.f90

    r5779 r5790  
    1818SUBROUTINE histprecip_precld( &
    1919           klon, dtime, iftop, paprsdn, paprsup, pplay, zt, ztupnew, zq, &
    20            zmqc, zneb, znebprecip, znebprecipclr, flsed, flsed_lincont, flsed_circont, &
     20           zmqc, zneb, znebprecip, znebprecipclr, flsed, flsed_cont, &
    2121           zrfl, zrflclr, zrflcld, zifl, ziflclr, ziflcld, dqreva, dqssub &
    2222           )
     
    4545REAL,    INTENT(INOUT), DIMENSION(klon) :: zmqc           !--specific humidity in the precipitation falling from the upper layer [kg/kg]
    4646REAL,    INTENT(IN),    DIMENSION(klon) :: flsed          !--sedimentated ice flux [kg/s/m2]
    47 REAL,    INTENT(IN),    DIMENSION(klon) :: flsed_lincont  !--linear contrails sedimentated ice flux [kg/s/m2]
    48 REAL,    INTENT(IN),    DIMENSION(klon) :: flsed_circont  !--contrail cirrus sedimentated ice flux [kg/s/m2]
     47REAL,    INTENT(IN),    DIMENSION(klon) :: flsed_cont     !--contrails sedimentated ice flux [kg/s/m2]
    4948
    5049REAL,    INTENT(IN),    DIMENSION(klon) :: zneb           !--cloud fraction IN THE LAYER ABOVE [-]
     
    134133    !--If the sedimentation of ice crystals is activated, the falling ice is sublimated and
    135134    !--added to the total water content of the gridbox
    136     IF ( (flsed(i) + flsed_lincont(i) + flsed_circont(i)) .GT. 0. ) THEN
    137       qice_sedim = (flsed(i) + flsed_lincont(i) + flsed_circont(i)) &
     135    IF ( (flsed(i) + flsed_cont(i)) .GT. 0. ) THEN
     136      qice_sedim = (flsed(i) + flsed_cont(i)) &
    138137          / ( paprsdn(i) - paprsup(i) ) * RG * dtime
    139138
     
    757756           klon, dtime, iftop, paprsdn, paprsup, pplay, temp, tempupnew, qvap, &
    758757           qprecip, precipfracclr, precipfraccld, qvapclrup, qtotupnew, &
    759            flsed, flsed_lincont, flsed_circont, &
     758           flsed, flsed_cont, &
    760759           cldfra, qvc, qliq, qice, &
    761760           rain, rainclr, raincld, snow, snowclr, snowcld, &
     
    793792REAL,    INTENT(IN),    DIMENSION(klon) :: qtotupnew      !--total specific humidity IN THE LAYER ABOVE [kg/kg]
    794793REAL,    INTENT(IN),    DIMENSION(klon) :: flsed          !--sedimentated ice water flux [kg/s/m2]
    795 REAL,    INTENT(IN),    DIMENSION(klon) :: flsed_lincont  !--sedimentated ice water flux [kg/s/m2]
    796 REAL,    INTENT(IN),    DIMENSION(klon) :: flsed_circont  !--sedimentated ice water flux [kg/s/m2]
     794REAL,    INTENT(IN),    DIMENSION(klon) :: flsed_cont     !--sedimentated ice water flux [kg/s/m2]
    797795
    798796REAL,    INTENT(INOUT), DIMENSION(klon) :: cldfra         !--cloud fraction at the beginning of lscp - used only if the cloud properties are advected [-]
     
    896894  cpw = RCPD * RVTMP2
    897895  DO i = 1, klon
    898     IF ( (flsed(i) + flsed_lincont(i) + flsed_circont(i)) .GT. 0. ) THEN
    899       qice_sedim = (flsed(i) + flsed_lincont(i) + flsed_circont(i)) / dhum_to_dflux(i)
     896    IF ( (flsed(i) + flsed_cont(i)) .GT. 0. ) THEN
     897      qice_sedim = (flsed(i) + flsed_cont(i)) / dhum_to_dflux(i)
    900898      !--No condensed water so cp=cp(vapor+dry air)
    901899      !-- RVTMP2=rcpv/rcpd-1
     
    10051003    !--If the sedimentation of ice crystals is activated, the falling ice is sublimated and
    10061004    !--added to the total water content of the gridbox
    1007     IF ( (flsed(i) + flsed_lincont(i) + flsed_circont(i)) .GT. 0. ) THEN
    1008       qice_sedim = (flsed(i) + flsed_lincont(i) + flsed_circont(i)) / dhum_to_dflux(i)
     1005    IF ( (flsed(i) + flsed_cont(i)) .GT. 0. ) THEN
     1006      qice_sedim = (flsed(i) + flsed_cont(i)) / dhum_to_dflux(i)
    10091007      !--Vapor is updated after evaporation/sublimation (it is increased)
    10101008      qvap(i) = qvap(i) + qice_sedim
Note: See TracChangeset for help on using the changeset viewer.