1 | MODULE 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 | !> Inter-moment relation set of parameters for the spherical mode. |
---|
30 | TYPE(aprm), PUBLIC, SAVE :: mmp_asp |
---|
31 | !> Inter-moment relation set of parameters for the fractal mode. |
---|
32 | TYPE(aprm), PUBLIC, SAVE :: mmp_afp |
---|
33 | |
---|
34 | !> Data set for @f$<Q>_{SF}^{M0}@f$. |
---|
35 | TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbsf0 |
---|
36 | !> Extended values of [[mmp_gcm(module):mmp_qbsf0(variable)]] dataset. |
---|
37 | REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf0_e |
---|
38 | !> Data set for @f$<Q>_{SF}^{M3}@f$. |
---|
39 | TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbsf3 |
---|
40 | !> Extended values of [[mmp_gcm(module):mmp_qbsf3(variable)]] dataset. |
---|
41 | REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf3_e |
---|
42 | !> Data set for @f$<Q>_{FF}^{M0}@f$. |
---|
43 | TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbff0 |
---|
44 | !> Extended values of [[mmp_gcm(module):mmp_qbff0(variable)]] dataset. |
---|
45 | REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbff0_e |
---|
46 | |
---|
47 | !> Data set for linear interpolation of transfert probability (M0/CO). |
---|
48 | TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco0p |
---|
49 | !> Data set for linear interpolation of transfert probability (M3/CO). |
---|
50 | TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco3p |
---|
51 | !> Data set for linear interpolation of transfert probability (M0/FM). |
---|
52 | TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm0p |
---|
53 | !> Data set for linear interpolation of transfert probability (M3/FM). |
---|
54 | TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm3p |
---|
55 | |
---|
56 | !> \(b_{0}^{t}\) coefficients for Free-molecular regime kernel approximation. |
---|
57 | 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/) |
---|
58 | !> \(b_{3}^{t}\) coefficients for Free-molecular regime kernel approximation. |
---|
59 | 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/) |
---|
60 | |
---|
61 | !> Spherical probability transfert control flag. |
---|
62 | LOGICAL, SAVE :: mmp_w_ps2s = .true. |
---|
63 | !> Aerosol electric charge correction control flag. |
---|
64 | LOGICAL, SAVE :: mmp_w_qe = .true. |
---|
65 | |
---|
66 | CONTAINS |
---|
67 | |
---|
68 | SUBROUTINE abort_program(err) |
---|
69 | !! Dump error message and abort the program. |
---|
70 | TYPE(error), INTENT(in) :: err !! Error object. |
---|
71 | WRITE(stderr,'(a)') "ERROR: "//TRIM(err%msg) |
---|
72 | CALL EXIT(err%id) |
---|
73 | END SUBROUTINE abort_program |
---|
74 | |
---|
75 | END MODULE MMP_GLOBALS |
---|