Ignore:
Timestamp:
Jan 17, 2025, 6:12:48 PM (13 days ago)
Author:
aborella
Message:

Added dependance of rei to contrail fraction

File:
1 edited

Legend:

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

    r5400 r5488  
    99    reliq_pi, reice_pi, scdnc, cldncl, reffclwtop, lcc, reffclws, &
    1010    reffclwc, cldnvi, lcc3d, lcc3dcon, lcc3dstra, icc3dcon, icc3dstra,  &
    11     icefrac_optics, dNovrN, ptconv,rnebcon, ccwcon)
     11    icefrac_optics, dNovrN, ptconv, rnebcon, ccwcon, rcontrail)
    1212
    1313  USE lmdz_cloud_optics_prop_ini , ONLY : flag_aerosol, ok_cdnc
     
    2828  USE lmdz_cloud_optics_prop_ini , ONLY : ok_icefra_lscp, rei_max, rei_min
    2929  USE lmdz_cloud_optics_prop_ini , ONLY : zepsec, novlp, iflag_ice_thermo, ok_new_lscp
     30  USE lmdz_cloud_optics_prop_ini , ONLY : ok_plane_contrail, re_ice_crystals_contrails
    3031 
    3132
     
    6970
    7071  LOGICAL, INTENT(IN) :: ptconv(klon, klev) ! flag for grid points affected by deep convection
     72
     73  REAL, INTENT(IN) :: rcontrail(klon, klev) ! ratio of contrails to total cloud fraction, used only if ok_plane_contrail=y [-]
    7174
    7275  ! inout:
     
    333336
    334337          IF (zfiwp_var==0. .OR. rei<=0.) rei = 1.
     338          IF ( ok_plane_contrail ) THEN
     339            !--If contrails are activated, rei is a weighted average between the natural
     340            !--rei and the contrails rei, with the weights being the fraction of natural
     341            !--vs contrail cirrus in the gridbox
     342            rei = rei * ( 1. - rcontrail(i,k) ) + re_ice_crystals_contrails * rcontrail(i,k)
     343          ENDIF
    335344          pcldtaupi(i, k) = 3.0/2.0*zflwp_var/rad_chaud_pi(i, k) + &
    336345            zfiwp_var*(3.448E-03+2.431/rei)
     
    442451        IF (zflwp_var==0.) rel = 1.
    443452        IF (zfiwp_var==0. .OR. rei<=0.) rei = 1.
     453        IF ( ok_plane_contrail ) THEN
     454          !--If contrails are activated, rei is a weighted average between the natural
     455          !--rei and the contrails rei, with the weights being the fraction of natural
     456          !--vs contrail cirrus in the gridbox
     457          rei = rei * ( 1. - rcontrail(i,k) ) + re_ice_crystals_contrails * rcontrail(i,k)
     458        ENDIF
    444459        pcltau(i, k) = 3.0/2.0*(zflwp_var/rel) + zfiwp_var*(3.448E-03+2.431/ &
    445460          rei)
Note: See TracChangeset for help on using the changeset viewer.