Ignore:
Timestamp:
Nov 7, 2024, 11:09:51 AM (2 weeks ago)
Author:
debatzbr
Message:

Final clean and debug for the microphysical model

File:
1 edited

Legend:

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

    r3318 r3496  
    112112      mm_ccn_vsed(:) = wsettle(mm_play,mm_temp,mm_zlay,mm_drho,mm_drad)
    113113
    114       ! Computes flux [kg.m-2.s-1] and precipitation [kg.m-2.iphysiq] of ccn
     114      ! Computes flux [kg.m-2.s-1] and precipitation [kg.m-2] of ccn
    115115      mm_ccn_flux(:) = get_mass_flux(mm_rhoaer,mm_m3ccn(:))
    116116      mm_ccn_prec = SUM(zdm3n*mm_dzlev*mm_rhoaer)
    117117
    118       ! Computes flux [kg.m-2.s-1] and precipitation [kg.m-2.iphysiq] of ices
     118      ! Computes flux [kg.m-2.s-1] and precipitation [kg.m-2] of ices
    119119      DO i = 1, mm_nesp
    120120        mm_ice_fluxes(:,i) = get_mass_flux(mm_xESPS(i)%rho,(3._mm_wp*mm_m3ice(:,i))/(4._mm_wp*mm_pi))
     
    729729    REAL(kind=mm_wp), INTENT(in) :: rad !! Radius of the particle (m).
    730730    REAL(kind=mm_wp) :: w               !! Settling velocity (\(m.s^{-1}\)).
    731     REAL(kind=mm_wp) :: Us, Fc, kn
     731    REAL(kind=mm_wp) :: Us, Fc, kn, wtmp, wmax
    732732    REAL(kind=mm_wp), PARAMETER :: ra = 1.75e-10_mm_wp
    733733   
     
    743743    ! Computes settling velocity (correction factor : x3.0)
    744744    w = Us * Fc * 3._mm_wp
     745
     746    ! Imposes a velocity limit
     747    wmax = 20._mm_wp ! 20 m/s [Lorenz 1993]
     748    wtmp = (1._mm_wp / w) + (1._mm_wp / wmax)
     749    w = 1._mm_wp / wtmp
    745750  END FUNCTION wsettle
    746751
Note: See TracChangeset for help on using the changeset viewer.