1 | ! Copyright 2013-2015,2017,2022 Université de Reims Champagne-Ardenne |
---|
2 | ! Contributor: J. Burgalat (GSMA, URCA) |
---|
3 | ! email of the author : jeremie.burgalat@univ-reims.fr |
---|
4 | ! |
---|
5 | ! This software is a computer program whose purpose is to compute |
---|
6 | ! microphysics processes using a two-moments scheme. |
---|
7 | ! |
---|
8 | ! This library is governed by the CeCILL-B license under French law and |
---|
9 | ! abiding by the rules of distribution of free software. You can use, |
---|
10 | ! modify and/ or redistribute the software under the terms of the CeCILL-B |
---|
11 | ! license as circulated by CEA, CNRS and INRIA at the following URL |
---|
12 | ! "http://www.cecill.info". |
---|
13 | ! |
---|
14 | ! As a counterpart to the access to the source code and rights to copy, |
---|
15 | ! modify and redistribute granted by the license, users are provided only |
---|
16 | ! with a limited warranty and the software's author, the holder of the |
---|
17 | ! economic rights, and the successive licensors have only limited |
---|
18 | ! liability. |
---|
19 | ! |
---|
20 | ! In this respect, the user's attention is drawn to the risks associated |
---|
21 | ! with loading, using, modifying and/or developing or reproducing the |
---|
22 | ! software by the user in light of its specific status of free software, |
---|
23 | ! that may mean that it is complicated to manipulate, and that also |
---|
24 | ! therefore means that it is reserved for developers and experienced |
---|
25 | ! professionals having in-depth computer knowledge. Users are therefore |
---|
26 | ! encouraged to load and test the software's suitability as regards their |
---|
27 | ! requirements in conditions enabling the security of their systems and/or |
---|
28 | ! data to be ensured and, more generally, to use and operate it in the |
---|
29 | ! same conditions as regards security. |
---|
30 | ! |
---|
31 | ! The fact that you are presently reading this means that you have had |
---|
32 | ! knowledge of the CeCILL-B license and that you accept its terms. |
---|
33 | |
---|
34 | !! file: mm_interfaces.f90 |
---|
35 | !! summary: Interfaces module for external functions |
---|
36 | !! author: J. Burgalat |
---|
37 | !! date: 2013-2015,2017,2022 |
---|
38 | |
---|
39 | MODULE MM_INTERFACES |
---|
40 | !! Interfaces to external functions. |
---|
41 | !! |
---|
42 | !! The module contains the definitions of all "external" functions used by moments model which are |
---|
43 | !! left to the developer's responsibility. |
---|
44 | !! |
---|
45 | !! # Functions |
---|
46 | !! |
---|
47 | !! - [[mm_interfaces(module):mm_alpha_s(interface)]] should compute the inter-moments relation coefficient |
---|
48 | !! as a function of the moment's order for the spherical mode. |
---|
49 | !! - [[mm_interfaces(module):mm_alpha_f(interface)]] should perform the same computations as |
---|
50 | !! [[mm_interfaces(module):mm_alpha_s(interface)]] but for the fractal mode. |
---|
51 | !! - [[mm_interfaces(module):mm_ps2s(interface)]] should compute the probability for particles of the |
---|
52 | !! spherical mode to remain in that mode during coagulation process. |
---|
53 | !! - [[mm_interfaces(module):mm_qmean(interface)]] should compute the mean eletric charge correction to be |
---|
54 | !! applied on each coagulation sub-kernels computed in mm_haze module. |
---|
55 | !! - [[mm_interfaces(module):mm_get_btk(interface)]] should compute the \(b_{k}^{T}\) coefficient of the |
---|
56 | !! free-molecular regime. |
---|
57 | USE MM_MPREC |
---|
58 | IMPLICIT NONE |
---|
59 | |
---|
60 | PUBLIC |
---|
61 | |
---|
62 | INTERFACE |
---|
63 | |
---|
64 | PURE FUNCTION mm_alpha_s(k) RESULT (res) |
---|
65 | !! Inter-moment relation for spherical aerosols size distribution law. |
---|
66 | !! |
---|
67 | !! The method computes the relation between the kth order moment and the 0th order moment: |
---|
68 | !! $$ \dfrac{M_{k}}{M_{0}} = r_{C}^{k} \times \alpha(k,a_{1},...a_{n}) $$ |
---|
69 | IMPORT mm_wp |
---|
70 | REAL(kind=mm_wp), INTENT(in) :: k !! Order of the moment. |
---|
71 | REAL(kind=mm_wp) :: res !! Alpha value. |
---|
72 | END FUNCTION mm_alpha_s |
---|
73 | |
---|
74 | PURE FUNCTION mm_alpha_f(k) RESULT (res) |
---|
75 | !! Inter-moment relation for fractal aerosols size distribution law. |
---|
76 | !! |
---|
77 | !! The method computes the relation between the kth order moment and the 0th order moment: |
---|
78 | !! $$ \dfrac{M_{k}}{M_{0}} = r_{C}^{k} \times \alpha(k,a_{1},...a_{n}) $$ |
---|
79 | IMPORT mm_wp |
---|
80 | REAL(kind=mm_wp), INTENT(in) :: k !! Order of the moment. |
---|
81 | REAL(kind=mm_wp) :: res !! Alpha value. |
---|
82 | END FUNCTION mm_alpha_f |
---|
83 | |
---|
84 | FUNCTION mm_ps2s(rcs,k,flow,t,p) RESULT(res) |
---|
85 | !! Get the proportion of aerosols that remains in the spherical mode during SS coagulation. |
---|
86 | IMPORT mm_wp |
---|
87 | REAL(kind=mm_wp), INTENT(in) :: rcs !! Characteristic radius of the spherical size-distribution (m). |
---|
88 | REAL(kind=mm_wp), INTENT(in) :: t !! Temperature (K). |
---|
89 | REAL(kind=mm_wp), INTENT(in) :: p !! Pressure level (Pa). |
---|
90 | INTEGER, INTENT(in) :: k !! Order of the moment (0 or 3). |
---|
91 | INTEGER, INTENT(in) :: flow !! Flow regime (0: continuous, 1: Free molecular). |
---|
92 | REAL(kind=mm_wp) :: res !! Proportion of spherical particles that remains in the spherical mode. |
---|
93 | END FUNCTION mm_ps2s |
---|
94 | |
---|
95 | FUNCTION mm_qmean(rc1,rc2,order,modes,temp,pres) RESULT(res) |
---|
96 | !! Get the electric correction for coagulation kernel. |
---|
97 | !! |
---|
98 | !! The method computes the eletric charging correction to apply to the coagulation |
---|
99 | !! kernel as a function of the temperature, pressure and the characteristic radius of |
---|
100 | !! the mode involved in the coagulation. |
---|
101 | !! |
---|
102 | !! Modes are referred by a two letters uppercase string with the combination of: |
---|
103 | !! |
---|
104 | !! - S : spherical mode |
---|
105 | !! - F : fractal mode |
---|
106 | !! |
---|
107 | !! For example, SS means intra-modal coagulation for spherical particles. |
---|
108 | IMPORT mm_wp |
---|
109 | REAL(kind=mm_wp), INTENT(in) :: rc1 !! Characteristic radius of the the first distribution (m). |
---|
110 | REAL(kind=mm_wp), INTENT(in) :: rc2 !! Characteristic radius of the the second distribution (m). |
---|
111 | INTEGER, INTENT(in) :: order !! Moment's order (0 or 3). |
---|
112 | CHARACTER(len=2), INTENT(in) :: modes !! Interaction mode (a combination of [S,F]). |
---|
113 | REAL(kind=mm_wp), INTENT(in) :: temp !! Temperature (K). |
---|
114 | REAL(kind=mm_wp), INTENT(in) :: pres !! Pressure level (Pa). |
---|
115 | REAL(kind=mm_wp) :: res !! Electric charging correction. |
---|
116 | END FUNCTION mm_qmean |
---|
117 | |
---|
118 | PURE FUNCTION mm_get_btk(t,k) RESULT(res) |
---|
119 | !! Get the \(b_{k}^{T}\) coefficient of the Free Molecular regime. |
---|
120 | !! |
---|
121 | !! The method computes and returns the value of the pre-factor \(b_{k}^{T}\) used to |
---|
122 | !! approximate free-molecular regime coagulation kernels. |
---|
123 | !! @note |
---|
124 | !! For more details about \(b_{k}^{T}\) coefficient, please read the |
---|
125 | !! [scientific documentation](page/haze.html#free-molecular). |
---|
126 | !! |
---|
127 | !! @attention |
---|
128 | !! In its current version, the model only deals with fixed values of __k__ and __T__. |
---|
129 | !! __k__ can take the values (0,3) and, __T__, the values within [1,5]. |
---|
130 | IMPORT mm_wp |
---|
131 | INTEGER, INTENT(in) :: t !! Interaction identifier. |
---|
132 | INTEGER, INTENT(in) :: k !! Moment order. |
---|
133 | REAL(kind=mm_wp) :: res !! \(b_{k}^{T}\) value. |
---|
134 | END FUNCTION mm_get_btk |
---|
135 | |
---|
136 | |
---|
137 | ELEMENTAL FUNCTION mm_eta_g(t) RESULT (res) |
---|
138 | !! Get the air viscosity at a given temperature. |
---|
139 | IMPORT mm_wp |
---|
140 | REAL(kind=mm_wp), INTENT(in) :: t !! Temperature (K). |
---|
141 | REAL(kind=mm_wp) :: res !! Air viscosity at given temperature (\(Pa.s^{-1}\)). |
---|
142 | END FUNCTION mm_eta_g |
---|
143 | |
---|
144 | ELEMENTAL FUNCTION mm_lambda_g(t,p) RESULT(res) |
---|
145 | !! Get the air mean free path at given temperature and pressure. |
---|
146 | IMPORT mm_wp |
---|
147 | REAL(kind=mm_wp), INTENT(in) :: t !! Temperature (K). |
---|
148 | REAL(kind=mm_wp), INTENT(in) :: p !! Pressure level (Pa). |
---|
149 | REAL(kind=mm_wp) :: res !! Air mean free path (m). |
---|
150 | END FUNCTION mm_lambda_g |
---|
151 | |
---|
152 | END INTERFACE |
---|
153 | |
---|
154 | END MODULE MM_INTERFACES |
---|
155 | |
---|