source: trunk/LMDZ.TITAN/libf/phytitan/muphy_diag.F90 @ 2236

Last change on this file since 2236 was 1926, checked in by jvatant, 7 years ago

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 size: 3.7 KB
Line 
1MODULE muphy_diag
2  !! Microphysics diagnostcs vairables module.
3  !!
4  !! The module contains all the variables related to output diagnostics of the microphysics.
5  !! Such variables are not (and should not be) used as input in the GCM except for output data writing.
6  !!
7  !! The module also contains two methods:
8  !!
9  !! - ini_diag_arrays(ngrid,nlayer,nices)
10  !! - free_diag_arrays()
11
12  USE tracer_h
13  IMPLICIT NONE
14  REAL(kind=8), ALLOCATABLE, DIMENSION(:)     :: mmd_aer_prec   !! Aerosols precipitations (both modes) (m).
15  REAL(kind=8), ALLOCATABLE, DIMENSION(:)     :: mmd_ccn_prec   !! CCN precipitations (m).
16  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_aer_s_flux !! Spherical aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
17  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_aer_f_flux !! Fractal aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
18  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_ccn_flux   !! CCN mass flux (\(kg.m^{-2}.s^{-1}\)).
19  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:,:) :: mmd_ice_fluxes !! Ice sedimentation fluxes (\(kg.m^{-2}.s^{-1}\)).
20  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:,:) :: mmd_gazs_sat   !! Condensible gaz saturation ratios (--).
21  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_ice_prec   !! Ice precipitations (m).
22  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_rc_sph     !! Spherical mode characteristic radius (m).
23  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_rc_fra     !! Fractal mode characteristic radius (m).
24  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_rc_cld     !! Cloud drop radius (m).
25
26  !$OMP TRHEADPRIVATE(mmd_aer_prec,mmd_ccnprec,mmd_aer_s_flux,mmd_aer_f_flux,mmd_ccn_flux,mmd_ice_fluxes)
27  !$OMP TRHEADPRIVATE(mmd_gazs_sat,mmd_ice_prec,mmd_rc_sph,mmd_rc_fra,mmd_rc_cld)
28
29  CONTAINS
30
31  SUBROUTINE ini_diag_arrays(ngrid,nlayer,nices)
32    !! Initialize the variables associated to microphysics diagnostics.
33    INTEGER, INTENT(in) :: ngrid  !! Number of points of the horizontal grid.
34    INTEGER, INTENT(in) :: nlayer !! Number of points of the vertical grid (layers).
35    INTEGER, INTENT(in) :: nices  !! Number of condensible species (cloud microphysics).
36    ALLOCATE(mmd_aer_prec(ngrid))
37    ALLOCATE(mmd_ccn_prec(ngrid))
38    ALLOCATE(mmd_aer_s_flux(ngrid,nlayer))
39    ALLOCATE(mmd_aer_f_flux(ngrid,nlayer))
40    ALLOCATE(mmd_ccn_flux(ngrid,nlayer))
41    ALLOCATE(mmd_ice_fluxes(ngrid,nlayer,nices))
42    ALLOCATE(mmd_gazs_sat(ngrid,nlayer,nices))
43    ALLOCATE(mmd_ice_prec(ngrid,nices))
44    ALLOCATE(mmd_rc_sph(ngrid,nlayer))
45    ALLOCATE(mmd_rc_fra(ngrid,nlayer))
46    ALLOCATE(mmd_rc_cld(ngrid,nlayer))
47
48    mmd_aer_prec(:)       = 0d0
49    mmd_ccn_prec(:)       = 0d0
50    mmd_aer_s_flux(:,:)   = 0d0
51    mmd_aer_f_flux(:,:)   = 0d0
52    mmd_ccn_flux(:,:)     = 0d0
53    mmd_ice_fluxes(:,:,:) = 0d0
54    mmd_gazs_sat(:,:,:)   = 0d0
55    mmd_ice_prec(:,:)     = 0d0
56    mmd_rc_sph(:,:)       = 0d0
57    mmd_rc_fra(:,:)       = 0d0
58    mmd_rc_cld(:,:)       = 0d0
59     
60  END SUBROUTINE ini_diag_arrays
61
62  SUBROUTINE free_diag_arrays()
63    !! Free memory of the variables associated to microphysics diagnostics.
64    IF (ALLOCATED(mmd_aer_prec))   DEALLOCATE(mmd_aer_prec)
65    IF (ALLOCATED(mmd_ccn_prec))   DEALLOCATE(mmd_ccn_prec)
66    IF (ALLOCATED(mmd_aer_s_flux)) DEALLOCATE(mmd_aer_s_flux)
67    IF (ALLOCATED(mmd_aer_f_flux)) DEALLOCATE(mmd_aer_f_flux)
68    IF (ALLOCATED(mmd_ccn_flux))   DEALLOCATE(mmd_ccn_flux)
69    IF (ALLOCATED(mmd_ice_fluxes)) DEALLOCATE(mmd_ice_fluxes)
70    IF (ALLOCATED(mmd_gazs_sat))   DEALLOCATE(mmd_gazs_sat)
71    IF (ALLOCATED(mmd_ice_prec))   DEALLOCATE(mmd_ice_prec)
72    IF (ALLOCATED(mmd_rc_sph))     DEALLOCATE(mmd_rc_sph)
73    IF (ALLOCATED(mmd_rc_fra))     DEALLOCATE(mmd_rc_fra)
74    IF (ALLOCATED(mmd_rc_cld))     DEALLOCATE(mmd_rc_cld)
75  END SUBROUTINE free_diag_arrays
76END MODULE muphy_diag
Note: See TracBrowser for help on using the repository browser.