source: trunk/LMDZ.TITAN/libf/muphytitan/mmp_globals.f90 @ 1918

Last change on this file since 1918 was 1897, checked in by jvatant, 7 years ago

Making Titan's hazy again - part II
+ Major updates of J.Burgalat YAMMS library and optical coupling, including :
++ Added the routines for haze optics inside YAMMS
++ Calling rad. transf. with interactive haze is plugged
in but should stay unactive as long as the microphysics is
in test phase : cf "uncoupl_optic_haze" flag : true for now !
++ Also some sanity checks for negative tendencies and
some others upkeep of YAMMS model
+ Also added a temporary CPP key USE_QTEST in physiq_mod
that enables to have microphysical tendencies separated
from dynamics for debugging and test phases
-- JVO and JB

File size: 4.1 KB
Line 
1MODULE MMP_GLOBALS
2  !! Interface to YAMMS for the LMDZ GCM.
3  USE MM_LIB
4  USE DATASETS
5  IMPLICIT NONE
6
7  PUBLIC
8
9  !> Alpha function parameters.
10  !!
11  !! It stores the parameters of the inter-moments relation functions.
12  !!
13  !! The inter-moments relation function is represented by the sum of exponential
14  !! quadratic expressions:
15  !!
16  !! $$
17  !! \displaystyle \alpha(k) = \sum_{i=1}^{n} \exp\left( a_{i}\times k^{2} +
18  !! b_{i}\times k^{2} +c_{i}\right)
19  !! $$
20  TYPE, PUBLIC :: aprm
21    !> Quadratic coefficients of the quadratic expressions.
22    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: a
23    !> Linear coefficients of the quadratic expressions.
24    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: b
25    !> Free term of the quadratic expressions.
26    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: c
27  END TYPE
28
29  !> Size distribution parameters derived type.
30  !!
31  !! It stores the parameters of the size distribution law for Titan.
32  !!
33  !! The size distribution law is represented by the minimization of a sum of
34  !! power law functions:
35  !!
36  !! $$
37  !! \displaystyle n\left(r\right) = \frac{A_{0}}{C+\sum_{i=1}^{n} A_{i}\times
38  !!                                    \left(\frac{r}{r_{c}}\right)^{-b_{i}}}
39  !! $$
40  TYPE, PUBLIC :: nprm
41    !> Scaling factor.
42    REAL(kind=mm_wp)                            :: a0
43    !> Characterisitic radius.
44    REAL(kind=mm_wp)                            :: rc
45    !> Additional constant to the sum of power law.
46    REAL(kind=mm_wp)                            :: c
47    !> Scaling factor of each power law.
48    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: a
49    !> Power of each power law.
50    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: b
51  END TYPE
52
53  !> Inter-moment relation set of parameters for the spherical mode.
54  TYPE(aprm), PUBLIC, SAVE :: mmp_asp
55  !> Inter-moment relation set of parameters for the fractal mode.
56  TYPE(aprm), PUBLIC, SAVE :: mmp_afp
57
58  !> Size-distribution law parameters of the spherical mode.
59  TYPE(nprm), PUBLIC, SAVE :: mmp_pns
60  !> Size-distribution law parameters of the fractal mode.
61  TYPE(nprm), PUBLIC, SAVE :: mmp_pnf
62
63  !> Data set for @f$<Q>_{SF}^{M0}@f$.
64  TYPE(dset2d), PUBLIC, SAVE, TARGET             :: mmp_qbsf0
65  !> Extended values of [[mmp_gcm(module):mmp_qbsf0(variable)]] dataset.
66  REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf0_e
67  !> Data set for @f$<Q>_{SF}^{M3}@f$.
68  TYPE(dset2d), PUBLIC, SAVE, TARGET             :: mmp_qbsf3
69  !> Extended values of [[mmp_gcm(module):mmp_qbsf3(variable)]] dataset.
70  REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf3_e
71  !> Data set for @f$<Q>_{FF}^{M0}@f$.
72  TYPE(dset2d), PUBLIC, SAVE, TARGET             :: mmp_qbff0
73  !> Extended values of [[mmp_gcm(module):mmp_qbff0(variable)]] dataset.
74  REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbff0_e
75 
76  !> Data set for linear interpolation of transfert probability (M0/CO).
77  TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco0p
78  !> Data set for linear interpolation of transfert probability (M3/CO).
79  TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco3p
80  !> Data set for linear interpolation of transfert probability (M0/FM).
81  TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm0p
82  !> Data set for linear interpolation of transfert probability (M3/FM).
83  TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm3p
84
85  !> \(b_{0}^{t}\) coefficients for Free-molecular regime kernel approximation.
86  REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(5) :: mmp_bt0 = (/1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp/)
87  !> \(b_{3}^{t}\) coefficients for Free-molecular regime kernel approximation.
88  REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(5) :: mmp_bt3 = (/1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp/)
89
90  !> Spherical probability transfert control flag.
91  LOGICAL, SAVE :: mmp_w_ps2s = .true.
92  !> Aerosol electric charge correction control flag.
93  LOGICAL, SAVE :: mmp_w_qe   = .true.
94
95
96  CONTAINS
97   
98  SUBROUTINE abort_program(err)
99    !! Dump error message and abort the program.
100    TYPE(error), INTENT(in) :: err !! Error object.
101    WRITE(stderr,'(a)') "ERROR: "//TRIM(err%msg)
102    CALL EXIT(err%id)
103  END SUBROUTINE abort_program
104
105END MODULE MMP_GLOBALS
Note: See TracBrowser for help on using the repository browser.