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_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
Note: See TracChangeset for help on using the changeset viewer.