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

Last change on this file since 3497 was 3497, checked in by debatzbr, 2 weeks ago

Add AC6H6 condensation in the microphysics

File size: 4.5 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) (\(kg.m^{-2}.s^{-1}\)).
15  REAL(kind=8), ALLOCATABLE, DIMENSION(:)     :: mmd_ccn_prec   !! CCN precipitations (\(kg.m^{-2}.s^{-1}\)).
16  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_aer_s_w    !! Spherical aerosol settling velocity (\(m.s^{-1}\)).
17  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_aer_f_w    !! Fractal aerosol settling velocity (\(m.s^{-1}\)).
18  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_ccn_w      !! CCN settling velocity (\(m.s^{-1}\)).
19  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_aer_s_flux !! Spherical aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
20  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_aer_f_flux !! Fractal aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
21  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_ccn_flux   !! CCN mass flux (\(kg.m^{-2}.s^{-1}\)).
22  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:,:) :: mmd_ice_fluxes !! Ice sedimentation fluxes (\(kg.m^{-2}.s^{-1}\)).
23  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:,:) :: mmd_gazs_sat   !! Condensible gaz saturation ratios (--).
24  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_ice_prec   !! Ice precipitations (\(kg.m^{-2}.s^{-1}\)).
25  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_rc_sph     !! Spherical mode characteristic radius (m).
26  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_rc_fra     !! Fractal mode characteristic radius (m).
27  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mmd_rc_cld     !! Cloud drop radius (m).
28
29  !$OMP THREADPRIVATE(mmd_aer_prec,mmd_ccn_prec,mmd_aer_s_w,mmd_aer_f_w,mmd_ccn_w,mmd_aer_s_flux,mmd_aer_f_flux,mmd_ccn_flux,mmd_ice_fluxes)
30  !$OMP THREADPRIVATE(mmd_gazs_sat,mmd_ice_prec,mmd_rc_sph,mmd_rc_fra,mmd_rc_cld)
31
32  CONTAINS
33
34  SUBROUTINE ini_diag_arrays(ngrid,nlayer,nices)
35    !! Initialize the variables associated to microphysics diagnostics.
36    INTEGER, INTENT(in) :: ngrid  !! Number of points of the horizontal grid.
37    INTEGER, INTENT(in) :: nlayer !! Number of points of the vertical grid (layers).
38    INTEGER, INTENT(in) :: nices  !! Number of condensible species (cloud microphysics).
39    ALLOCATE(mmd_aer_prec(ngrid))
40    ALLOCATE(mmd_ccn_prec(ngrid))
41    ALLOCATE(mmd_aer_s_w(ngrid,nlayer))
42    ALLOCATE(mmd_aer_f_w(ngrid,nlayer))
43    ALLOCATE(mmd_ccn_w(ngrid,nlayer))
44    ALLOCATE(mmd_aer_s_flux(ngrid,nlayer))
45    ALLOCATE(mmd_aer_f_flux(ngrid,nlayer))
46    ALLOCATE(mmd_ccn_flux(ngrid,nlayer))
47    ALLOCATE(mmd_ice_fluxes(ngrid,nlayer,nices))
48    ALLOCATE(mmd_gazs_sat(ngrid,nlayer,nices))
49    ALLOCATE(mmd_ice_prec(ngrid,nices))
50    ALLOCATE(mmd_rc_sph(ngrid,nlayer))
51    ALLOCATE(mmd_rc_fra(ngrid,nlayer))
52    ALLOCATE(mmd_rc_cld(ngrid,nlayer))
53
54    mmd_aer_prec(:)       = 0d0
55    mmd_ccn_prec(:)       = 0d0
56    mmd_aer_s_w(:,:)      = 0d0
57    mmd_aer_f_w(:,:)      = 0d0
58    mmd_ccn_w(:,:)        = 0d0
59    mmd_aer_s_flux(:,:)   = 0d0
60    mmd_aer_f_flux(:,:)   = 0d0
61    mmd_ccn_flux(:,:)     = 0d0
62    mmd_ice_fluxes(:,:,:) = 0d0
63    mmd_gazs_sat(:,:,:)   = 0d0
64    mmd_ice_prec(:,:)     = 0d0
65    mmd_rc_sph(:,:)       = 0d0
66    mmd_rc_fra(:,:)       = 0d0
67    mmd_rc_cld(:,:)       = 0d0
68     
69  END SUBROUTINE ini_diag_arrays
70
71  SUBROUTINE free_diag_arrays()
72    !! Free memory of the variables associated to microphysics diagnostics.
73    IF (ALLOCATED(mmd_aer_prec))   DEALLOCATE(mmd_aer_prec)
74    IF (ALLOCATED(mmd_ccn_prec))   DEALLOCATE(mmd_ccn_prec)
75    IF (ALLOCATED(mmd_aer_s_w))    DEALLOCATE(mmd_aer_s_w)
76    IF (ALLOCATED(mmd_aer_f_w))    DEALLOCATE(mmd_aer_f_w)
77    IF (ALLOCATED(mmd_ccn_w))      DEALLOCATE(mmd_ccn_w)
78    IF (ALLOCATED(mmd_aer_s_flux)) DEALLOCATE(mmd_aer_s_flux)
79    IF (ALLOCATED(mmd_aer_f_flux)) DEALLOCATE(mmd_aer_f_flux)
80    IF (ALLOCATED(mmd_ccn_flux))   DEALLOCATE(mmd_ccn_flux)
81    IF (ALLOCATED(mmd_ice_fluxes)) DEALLOCATE(mmd_ice_fluxes)
82    IF (ALLOCATED(mmd_gazs_sat))   DEALLOCATE(mmd_gazs_sat)
83    IF (ALLOCATED(mmd_ice_prec))   DEALLOCATE(mmd_ice_prec)
84    IF (ALLOCATED(mmd_rc_sph))     DEALLOCATE(mmd_rc_sph)
85    IF (ALLOCATED(mmd_rc_fra))     DEALLOCATE(mmd_rc_fra)
86    IF (ALLOCATED(mmd_rc_cld))     DEALLOCATE(mmd_rc_cld)
87  END SUBROUTINE free_diag_arrays
88END MODULE muphy_diag
Note: See TracBrowser for help on using the repository browser.