Changeset 3496


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

Final clean and debug for the microphysical model

Location:
trunk/LMDZ.TITAN/libf/muphytitan
Files:
4 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
  • trunk/LMDZ.TITAN/libf/muphytitan/mm_globals.f90

    r3318 r3496  
    429429  REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE, SAVE :: mm_drho
    430430
    431   !> Aerosols precipitations (kg.m-2.s-1).
     431  !> Aerosols precipitations (kg.m-2).
    432432  !!
    433433  !! Aerosols precipitations take into account both spherical and fractal modes.
     
    435435  REAL(kind=mm_wp), SAVE :: mm_aer_prec = 0._mm_wp
    436436
    437   !> CCN precipitations (kg.m-2.s-1).
     437  !> CCN precipitations (kg.m-2).
    438438  !! It is updated in [[mm_clouds(module):mm_cloud_microphysics(subroutine)]].
    439439  REAL(kind=mm_wp), SAVE :: mm_ccn_prec = 0._mm_wp
     
    505505  REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE, SAVE :: mm_ccn_flux
    506506
    507   !> Ice components precipitations (kg.m-2.s-1).
     507  !> Ice components precipitations (kg.m-2).
    508508  !!
    509509  !! It is a vector of [[mm_globals(module):mm_nesp(variable)]] values which share the same indexing
  • trunk/LMDZ.TITAN/libf/muphytitan/mm_methods.f90

    r3090 r3496  
    370370      res = (1.0e5 / pres) * exp(1.511e1 - 2.207e3/temp - 2.411e4/temp**2 + 7.744e5/temp**3 - 1.161e7/temp**4 + 6.763e7/temp**5)
    371371   
     372    ELSE IF(xESP%name == "AC6H6") THEN
     373      ! Fray and Schmidt (2009)
     374      res = (1.0e5 / pres) * exp(1.735e1 - 5.663e3/temp)
     375
    372376    ELSE IF(xESP%name == "HCN") THEN
    373377      ! Fray and Schmidt (2009)
     
    406410      res = (1.0e5 / pres) * exp(1.511e1 - 2.207e3/temp - 2.411e4/temp**2 + 7.744e5/temp**3 - 1.161e7/temp**4 + 6.763e7/temp**5)
    407411   
     412    ELSE IF(xESP%name == "AC6H6") THEN
     413      ! Fray and Schmidt (2009)
     414      res = (1.0e5 / pres) * exp(1.735e1 - 5.663e3/temp)
     415
    408416    ELSE IF(xESP%name == "HCN") THEN
    409417      ! Fray and Schmidt (2009)
  • trunk/LMDZ.TITAN/libf/muphytitan/mm_microphysic.f90

    r3318 r3496  
    186186    !! microphysics is disabled (see [[mm_globals(module):mm_w_clouds(variable)]] documentation).
    187187    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).
     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}\)).
    190190    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_s_w    !! Spherical aerosol settling velocity (\(m.s^{-1}\)).
    191191    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_f_w    !! Fractal aerosol settling velocity (\(m.s^{-1}\)).
     
    196196    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: ice_fluxes !! Ice sedimentation fluxes (\(kg.m^{-2}.s^{-1}\)).
    197197    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: gazs_sat   !! Condensible gaz saturation ratios (--).
    198     REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ice_prec   !! Ice precipitations (kg.m-2.s-1).
     198    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ice_prec   !! Ice precipitations (\(kg.m^{-2}.s^{-1}\)).
    199199
    200200    IF (PRESENT(aer_prec))   aer_prec   = ABS(mm_aer_prec) / dt
Note: See TracChangeset for help on using the changeset viewer.