Ignore:
Timestamp:
Apr 3, 2025, 4:53:58 PM (3 months ago)
Author:
aborella
Message:

Removed deep convection clouds from prognostic cloud properties

File:
1 edited

Legend:

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

    r5601 r5602  
    88SUBROUTINE lscp(klon,klev,dtime,missing_val,            &
    99     paprs, pplay, omega, temp, qt, ql_seri, qi_seri,   &
    10      ptconv, ratqs, sigma_qtherm,                       &
     10     ptconv, cldfracv, qcondcv, ratqs, sigma_qtherm,    &
    1111     d_t, d_q, d_ql, d_qi, rneb, rneblsvol,             &
    1212     pfraclr, pfracld,                                  &
     
    153153                                                                   ! CR: if iflag_ice_thermo=2, only convection is active
    154154  LOGICAL, DIMENSION(klon,klev),   INTENT(IN)   :: ptconv          ! grid points where deep convection scheme is active
     155  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: cldfracv        ! cloud fraction from deep convection [-]
     156  REAL, DIMENSION(klon,klev),      INTENT(IN)   :: qcondcv         ! in-cloud condensed specific humidity from deep convection [kg/kg]
    155157
    156158  !Inputs associated with thermal plumes
     
    741743
    742744                    CALL condensation_ice_supersat( &
    743                         klon, dtime, missing_val, &
    744                         pplay(:,k), paprs(:,k), paprs(:,k+1), &
     745                        klon, dtime, pplay(:,k), paprs(:,k), paprs(:,k+1), &
     746                        cldfracv(:,k), qcondcv(:,k), &
    745747                        cf_seri(:,k), qvc_seri(:,k), qliq_in, qice_in, &
    746748                        shear, tke_dissip(:,k), cell_area, stratomask(:,k), &
     
    949951
    950952    IF (ok_plane_contrail) THEN
    951       !--Contrails do not precipitate. We remove then from the variables temporarily
     953      !!--Contrails do not precipitate. We remove then from the variables temporarily
     954      !DO i = 1, klon
     955      !  rneb(i,k) = rneb(i,k) - contfra(i)
     956      !  zoliqi(i) = zoliqi(i) - ( qcont(i) - zqs(i) * contfra(i) )
     957      !ENDDO
     958      !--Contrails precipitate as natural clouds. We save the partition of ice
     959      !--between natural clouds and contrails
     960      !--NB. we use qcont as a temporary variable to save this partition
    952961      DO i = 1, klon
    953         rneb(i,k) = rneb(i,k) - contfra(i)
    954         zoliqi(i) = zoliqi(i) - ( qcont(i) - zqs(i) * contfra(i) )
     962        IF ( zoliqi(i) .GT. 0. ) THEN
     963          qcont(i) = ( qcont(i) - zqs(i) * contfra(i) ) / zoliqi(i)
     964        ELSE
     965          qcont(i) = 0.
     966        ENDIF
    955967      ENDDO
    956968    ENDIF
     
    9901002   
    9911003    IF (ok_plane_contrail) THEN
    992       !--Contrails are reintroduced in the variables
     1004      !!--Contrails are reintroduced in the variables
     1005      !DO i = 1, klon
     1006      !  rneb(i,k) = rneb(i,k) + contfra(i)
     1007      !  zoliqi(i) = zoliqi(i) + ( qcont(i) - zqs(i) * contfra(i) )
     1008      !ENDDO
     1009      !--Contrails fraction is left unchanged, but contrails water has changed
    9931010      DO i = 1, klon
    994         rneb(i,k) = rneb(i,k) + contfra(i)
    995         zoliqi(i) = zoliqi(i) + ( qcont(i) - zqs(i) * contfra(i) )
     1011        IF ( zoliqi(i) .LE. 0. ) THEN
     1012          contfra(i) = 0.
     1013          qcont(i) = 0.
     1014        ELSE
     1015          qcont(i) = zqs(i) * contfra(i) + zoliqi(i) * qcont(i)
     1016        ENDIF
    9961017      ENDDO
    9971018    ENDIF
Note: See TracChangeset for help on using the changeset viewer.