Ignore:
Timestamp:
Apr 26, 2024, 4:27:26 PM (7 months ago)
Author:
slebonnois
Message:

Titan PCM update : optics + microphysics

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/muphytitan/mm_microphysic.f90

    r3090 r3318  
    163163  END FUNCTION muphys_nocld
    164164
    165   SUBROUTINE mm_diagnostics(aer_prec,aer_s_w,aer_f_w,aer_s_flux,aer_f_flux,ccn_prec,ccn_w,ccn_flux,ice_prec,ice_fluxes,gazs_sat)
     165  SUBROUTINE mm_diagnostics(dt,aer_prec,aer_s_w,aer_f_w,aer_s_flux,aer_f_flux,ccn_prec,ccn_w,ccn_flux,ice_prec,ice_fluxes,gazs_sat)
    166166    !! Get various diagnostic fields of the microphysics.
    167167    !!
     
    185185    !! __ccnprec__, __iceprec__, __icefluxes__ and __gazsat__ are always set to 0 if clouds
    186186    !! microphysics is disabled (see [[mm_globals(module):mm_w_clouds(variable)]] documentation).
    187     REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: aer_prec   !! Aerosols precipitations (both modes) (m).
    188     REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: ccn_prec   !! CCN precipitations (m).
     187    REAL(kind=8), INTENT(IN)                                :: dt         !! Physics timestep (s).
     188    REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: aer_prec   !! Aerosols precipitations (both modes) (kg.m-2.s-1).
     189    REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: ccn_prec   !! CCN precipitations (kg.m-2.s-1).
    189190    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_s_w    !! Spherical aerosol settling velocity (\(m.s^{-1}\)).
    190191    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_f_w    !! Fractal aerosol settling velocity (\(m.s^{-1}\)).
     
    195196    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: ice_fluxes !! Ice sedimentation fluxes (\(kg.m^{-2}.s^{-1}\)).
    196197    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: gazs_sat   !! Condensible gaz saturation ratios (--).
    197     REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ice_prec   !! Ice precipitations (m).
    198 
    199     IF (PRESENT(aer_prec))   aer_prec   = ABS(mm_aer_prec)
     198    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ice_prec   !! Ice precipitations (kg.m-2.s-1).
     199
     200    IF (PRESENT(aer_prec))   aer_prec   = ABS(mm_aer_prec) / dt
    200201    IF (PRESENT(aer_s_w))    aer_s_w    = -mm_m3as_vsed(mm_nla:1:-1)
    201202    IF (PRESENT(aer_f_w))    aer_f_w    = -mm_m3af_vsed(mm_nla:1:-1)
     
    204205
    205206    IF (mm_w_clouds) THEN
    206       IF (PRESENT(ccn_prec))   ccn_prec   = ABS(mm_ccn_prec)
    207       IF (PRESENT(ice_prec))   ice_prec   = ABS(mm_ice_prec)
     207      IF (PRESENT(ccn_prec))   ccn_prec   = ABS(mm_ccn_prec) / dt
     208      IF (PRESENT(ice_prec))   ice_prec   = ABS(mm_ice_prec) / dt
    208209      IF (PRESENT(ccn_w))      ccn_w      = mm_ccn_vsed(mm_nla:1:-1)
    209210      IF (PRESENT(ccn_flux))   ccn_flux   = mm_ccn_flux(mm_nla:1:-1)
Note: See TracChangeset for help on using the changeset viewer.