Ignore:
Timestamp:
Aug 4, 2025, 3:03:07 PM (12 days ago)
Author:
aborella
Message:

Additional diags for contrails + simplified coupling between deep conv and cirrus clouds + small modifsin RRTM for RF of contrails alone

File:
1 edited

Legend:

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

    r5790 r5796  
    55
    66  SUBROUTINE call_cloud_optics_prop(klon, klev, ok_newmicro,&
    7        paprs, pplay, temp, radocond, picefra, pclc, &
     7       paprs, pplay, temp, radocond, picefra, pclf, pclc, &
    88    pcltau, pclemi, pch, pcl, pcm, pct, radocondwp, xflwp, xfiwp, xflwc, xfiwc, ok_aie, &
    99    mass_solu_aero, mass_solu_aero_pi, pcldtaupi, distcltop, temp_cltop, re, fl, reliq, reice, &
     
    1212    icefrac_optics, dNovrN, ptconv,rnebcon, ccwcon, &
    1313    !--AB contrails
    14     contfra, qice_cont, Nice_cont, pclc_nocont, &
     14    contfravol, contfra, qice_cont, Nice_cont, pclc_cont, &
    1515    pcltau_nocont, pclemi_nocont, pcltau_cont, pclemi_cont, pch_nocont, pct_cont, &
    16     xfiwp_nocont, xfiwc_nocont, reice_nocont)
     16    xfiwp_cont, xfiwc_cont, reice_cont, &
     17    missing_val)
    1718
    1819  ! Interface between the LMDZ physics monitor and the cloud properties calculation routines
     
    3435  ! input:
    3536  INTEGER, INTENT(IN) :: klon, klev      ! number of horizontal and vertical grid points
     37  REAL, INTENT(IN) :: missing_val
    3638  REAL, INTENT(IN) :: paprs(klon, klev+1)! pressure at bottom interfaces [Pa]
    3739  REAL, INTENT(IN) :: pplay(klon, klev)  ! pressure at the middle of layers [Pa]
     
    4850  REAL, INTENT(OUT) :: distcltop(klon,klev) ! distance from large scale cloud top [m]
    4951  REAL, INTENT(OUT) :: temp_cltop(klon,klev)!temperature at large scale cloud top [K]
     52  REAL, INTENT(IN) :: pclf(klon, klev)      ! cloud fraction for radiation [-]
    5053
    5154  LOGICAL, INTENT(IN) :: ptconv(klon, klev) ! flag for grid points affected by deep convection
     
    5356
    5457  ! inout:
    55   REAL, INTENT(INOUT) :: pclc(klon, klev) ! cloud fraction for radiation [-]
     58  REAL, INTENT(INOUT) :: pclc(klon, klev) ! cloud cover for radiation [-]
    5659
    5760  ! out:
     
    9598
    9699  !--AB for contrails. All these are used / outputed only if ok_plane_contrail=y
     100  REAL, INTENT(IN)  :: contfravol(klon, klev)    ! contrails volumic fraction [-]
    97101  REAL, INTENT(IN)  :: contfra(klon, klev)       ! contrails fraction [-]
    98102  REAL, INTENT(IN)  :: qice_cont(klon, klev)     ! contrails condensed water [kg/kg]
     
    100104  REAL, INTENT(OUT) :: pch_nocont(klon)          ! 2D high cloud cover without contrails[-]
    101105  REAL, INTENT(OUT) :: pct_cont(klon)            ! 2D total contrails cover[-]
    102   REAL, INTENT(OUT) :: xfiwp_nocont(klon)        ! ice water path (seen by radiation) without contrails [kg/m2]
    103   REAL, INTENT(OUT) :: xfiwc_nocont(klon, klev)  ! ice water content seen by radiation without contrails [kg/kg]
    104   REAL, INTENT(OUT) :: pclc_nocont(klon, klev)   ! cloud fraction for radiation without contrails [-]
     106  REAL, INTENT(OUT) :: xfiwp_cont(klon)          ! ice water path (seen by radiation) of contrails [kg/m2]
     107  REAL, INTENT(OUT) :: xfiwc_cont(klon, klev)    ! ice water content seen by radiation of contrails [kg/kg]
     108  REAL, INTENT(OUT) :: pclc_cont(klon, klev)     ! cloud fraction for radiation of contrails [-]
    105109  REAL, INTENT(OUT) :: pcltau_nocont(klon, klev) ! cloud optical depth without contrails [-]
    106110  REAL, INTENT(OUT) :: pclemi_nocont(klon, klev) ! cloud emissivity without contrails [-]
    107111  REAL, INTENT(OUT) :: pcltau_cont(klon, klev)   ! contrails optical depth [-]
    108112  REAL, INTENT(OUT) :: pclemi_cont(klon, klev)   ! contrails emissivity [-]
    109   REAL, INTENT(OUT) :: reice_nocont(klon, klev)  ! ice effective radius without contrails [micronts]
     113  REAL, INTENT(OUT) :: reice_cont(klon, klev)    ! ice effective radius of contrails [micronts]
    110114  !--AB
    111115
     
    131135
    132136  IF (ok_newmicro) THEN       
    133     CALL cloud_optics_prop(klon, klev, paprs, pplay, temp, radocond, picefra, pclc, &
     137    CALL cloud_optics_prop(klon, klev, paprs, pplay, temp, radocond, picefra, pclf, pclc, &
    134138    pcltau, pclemi, pch, pcl, pcm, pct, radocondwp, xflwp, xfiwp, xflwc, xfiwc, &
    135139    mass_solu_aero, mass_solu_aero_pi, pcldtaupi, distcltop, temp_cltop, re, fl, reliq, reice, &
     
    138142    icefrac_optics, dNovrN, ptconv,rnebcon, ccwcon, &
    139143    !--AB for contrails
    140     contfra, qice_cont, Nice_cont, pclc_nocont, pcltau_nocont, &
     144    contfravol, contfra, qice_cont, Nice_cont, pclc_cont, pcltau_nocont, &
    141145    pclemi_nocont, pcltau_cont, pclemi_cont, pch_nocont, pct_cont, &
    142     xfiwp_nocont, xfiwc_nocont, reice_nocont)
     146    xfiwp_cont, xfiwc_cont, reice_cont, &
     147    missing_val)
    143148  ELSE
    144149    CALL nuage (paprs, pplay, &
Note: See TracChangeset for help on using the changeset viewer.