Ignore:
Timestamp:
May 28, 2018, 11:47:03 PM (6 years ago)
Author:
jvatant
Message:

1) Microphysics diags / outputs :


+ Add supplementary diagnostics outputs for microphysics ( precip, flux, rc ... ) ( new muphy_diag.F90 module )
+ Correct the outputs of microphys tracers to be in X/m-3 to be comparable to "standard values"

+ Also update the deftank callphys.def with latest revs modifs for microphysics

2) Condensation / chemistry updates :


+ Moved chemistry AFTER microphysics

  • To have mufi condensation before photochem
  • Chemistry called last coherent with the fact that it brings back fields to equilibrium

+ If 2D chemistry, make zonally averaged fields go through mufi and chem condensation

to have non saturated profiles in input of photochemistry
( other 'short' processes neglected as 2D -> no diurnal cycle, just seasonal evolution )

+ Also corrected the positivity check ( took Mars GCM syntax ) after chemistry ( could previously lead to negs )

3) Noticed a weird behaviour ( bug? ) :


+ If generalize the use of arrays *_indx for tracers, to get rid of ugly "iq+nmicro",

it ends up with weird results / crash in optim mode ( ok in debug ) but didn't find out why ...

--JVO

File:
1 edited

Legend:

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

    r1897 r1926  
    202202    !! microphysics is disabled (see [[mm_globals(module):mm_w_clouds(variable)]] documentation).
    203203    REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: aer_prec   !! Aerosols precipitations (both modes) (m).
    204     REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: ccn_prec   !! CCN precipitations (m).
    205204    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_s_flux !! Spherical aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
    206205    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_f_flux !! Fractal aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
     206    REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: ccn_prec   !! CCN precipitations (m).
    207207    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ccn_flux   !! CCN mass flux (\(kg.m^{-2}.s^{-1}\)).
     208    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ice_prec   !! Ice precipitations (m).
    208209    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: ice_fluxes !! Ice sedimentation fluxes (\(kg.m^{-2}.s^{-1}\)).
    209210    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: gazs_sat   !! Condensible gaz saturation ratios (--).
    210     REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ice_prec   !! Ice precipitations (m).
    211211
    212212    IF (PRESENT(aer_prec))   aer_prec   = ABS(mm_aer_prec)
Note: See TracChangeset for help on using the changeset viewer.