1 | ! Copyright 2013-2015,2017 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_clouds.f90 |
---|
35 | !! summary: Clouds microphysics module |
---|
36 | !! author: J. Burgalat |
---|
37 | !! date: 2013-2015,2017 |
---|
38 | |
---|
39 | MODULE MM_CLOUDS |
---|
40 | !! Clouds microphysics module. |
---|
41 | !! |
---|
42 | !! The module contains all definitions of the microphysics processes related to clouds: |
---|
43 | !! |
---|
44 | !! - [nucleation](page/clouds.html#nucleation) |
---|
45 | !! - [condensation](page/clouds.html#condensation) |
---|
46 | !! - [sedimentation](page/clouds.html#sedimentation) |
---|
47 | !! |
---|
48 | !! |
---|
49 | !! The interface methods always use the global variables defined in [[mm_globals(module)]] when values |
---|
50 | !! (any kind, temperature, pressure, moments...) over the vertical grid are required. |
---|
51 | !! Consequently, all these functions only deals with output argument which are most of the time the |
---|
52 | !! tendencies of relevant variables on the atmospheric column. |
---|
53 | !! |
---|
54 | !! @note |
---|
55 | !! Tendencies returned by public methods are always defined from __TOP__ of the atmosphere to the |
---|
56 | !! __GROUND__. |
---|
57 | USE MM_MPREC |
---|
58 | USE MM_GLOBALS |
---|
59 | USE MM_METHODS |
---|
60 | IMPLICIT NONE |
---|
61 | |
---|
62 | PRIVATE |
---|
63 | |
---|
64 | PUBLIC :: mm_cloud_microphysics, mm_cloud_sedimentation, mm_cloud_nucond |
---|
65 | |
---|
66 | CONTAINS |
---|
67 | |
---|
68 | !============================================================================ |
---|
69 | ! CLOUDS MICROPHYSICS INTERFACE SUBROUTINE |
---|
70 | !============================================================================ |
---|
71 | |
---|
72 | SUBROUTINE mm_cloud_microphysics(dm0a,dm3a,dm0n,dm3n,dm3i,dgazs) |
---|
73 | !! Get the evolution of moments tracers through clouds microphysics processes. |
---|
74 | !! |
---|
75 | !! The subroutine is a wrapper to the clouds microphysics methods. It computes the tendencies of moments |
---|
76 | !! tracers for nucleation, condensation and sedimentation processes for the atmospheric column. |
---|
77 | !! |
---|
78 | !! @note |
---|
79 | !! Both __dm3i__ and __dgazs__ are 2D-array with the vertical layers in first dimension and the number |
---|
80 | !! of ice components in the second. |
---|
81 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm0a |
---|
82 | !! Tendency of the 0th order moment of the aerosols (fractal mode) (\(m^{-3}\)). |
---|
83 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm3a |
---|
84 | !! Tendency of the 3rd order moment of the aerosols distribution (fractal mode) (\(m^{3}.m^{-3}\)) . |
---|
85 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm0n |
---|
86 | !! Tendency of the 0th order moment of the aerosols distribution (fractal mode) (\(m^{-3}\)). |
---|
87 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm3n |
---|
88 | !! Tendency of the 3rd order moment of the ccn distribution (\(m^{3}.m^{-3}\)). |
---|
89 | REAL(kind=mm_wp), DIMENSION(:,:), INTENT(out) :: dm3i |
---|
90 | !! Tendencies of the 3rd order moments of each ice components (\(m^{3}.m^{-3}\)). |
---|
91 | REAL(kind=mm_wp), DIMENSION(:,:), INTENT(out) :: dgazs |
---|
92 | !! Tendencies of each condensible gaz species (\(mol.mol^{-1}\)). |
---|
93 | REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: zdm0n,zdm3n |
---|
94 | REAL(kind=mm_wp), DIMENSION(:,:), ALLOCATABLE :: zdm3i |
---|
95 | INTEGER :: i |
---|
96 | dm0a = 0._mm_wp ; dm3a = 0._mm_wp |
---|
97 | dm0n = 0._mm_wp ; dm3n = 0._mm_wp |
---|
98 | dm3i = 0._mm_wp ; dgazs = 0._mm_wp |
---|
99 | |
---|
100 | IF (mm_w_cloud_nucond) THEN |
---|
101 | ! Calls condensation/nucleation (and update saturation ratio diagnostic) |
---|
102 | call mm_cloud_nucond(dm0a,dm3a,dm0n,dm3n,dm3i,dgazs,mm_gazs_sat) |
---|
103 | ENDIF |
---|
104 | |
---|
105 | IF (mm_w_cloud_sed) THEN |
---|
106 | ! Calls sedimentation |
---|
107 | ALLOCATE(zdm0n(mm_nla),zdm3n(mm_nla),zdm3i(mm_nla,mm_nesp)) |
---|
108 | call mm_cloud_sedimentation(zdm0n,zdm3n,zdm3i) |
---|
109 | |
---|
110 | ! computes precipitations / ice fluxes |
---|
111 | mm_ccn_prec = SUM(zdm3n*mm_dzlev) |
---|
112 | mm_ccn_flux(:) = get_mass_flux(mm_rhoaer,mm_m3ccn(:)) |
---|
113 | |
---|
114 | DO i=1, mm_nesp |
---|
115 | mm_ice_prec(i) = SUM(zdm3i(:,i)*mm_dzlev) |
---|
116 | mm_ice_fluxes(:,i) = get_mass_flux(mm_xESPS(i)%rho,mm_m3ice(:,i)) |
---|
117 | ENDDO |
---|
118 | ! updates tendencies |
---|
119 | dm0n = dm0n + zdm0n |
---|
120 | dm3n = dm3n + zdm3n |
---|
121 | dm3i = dm3i + zdm3i |
---|
122 | ENDIF |
---|
123 | |
---|
124 | END SUBROUTINE mm_cloud_microphysics |
---|
125 | |
---|
126 | !----------------------------------------------------------------------------- |
---|
127 | ! NUCLEATION/CONDENSATION PROCESS RELATED METHODS |
---|
128 | !----------------------------------------------------------------------------- |
---|
129 | |
---|
130 | SUBROUTINE mm_cloud_nucond(dm0a,dm3a,dm0n,dm3n,dm3i,dgazs,gazsat) |
---|
131 | !! Get moments tendencies through nucleation/condensation/evaporation. |
---|
132 | !! |
---|
133 | !! The method is a wrapper of [[mm_clouds(module):nc_esp(subroutine)]] which computes the |
---|
134 | !! tendencies of tracers for all the condensible species given in the vector __xESPS__. |
---|
135 | !! |
---|
136 | !! @warning |
---|
137 | !! __xESPS__, __m3i__ and __gazes__ must share the same indexing. For example if __xESPS(IDX)__ |
---|
138 | !! corresponds to \(CH_{4}\) properties then __m3i(IDX)__ must be the total volume of solid |
---|
139 | !! \(CH_{4}\) (ice) and __gazs(IDX)__ its vapor mole fraction. |
---|
140 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm0a |
---|
141 | !! Tendency of the 0th order moment of the aerosols (fractal mode) (\(m^{-3}\)). |
---|
142 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm3a |
---|
143 | !! Tendency of the 3rd order moment of the aerosols distribution (fractal mode) (\(m^{3}.m^{-3}\)). |
---|
144 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm0n |
---|
145 | !! Tendency of the 0th order moment of the aerosols distribution (fractal mode) (\(m^{-3}\)). |
---|
146 | REAL(kind=mm_wp), DIMENSION(:), INTENT(out) :: dm3n |
---|
147 | !! Tendency of the 3rd order moment of the ccn distribution (\(m^{3}.m^{-3}\)). |
---|
148 | REAL(kind=mm_wp), DIMENSION(:,:), INTENT(out) :: dm3i |
---|
149 | !! Tendencies of the 3rd order moments of each ice components (\(m^{3}.m^{-3}\)). |
---|
150 | REAL(kind=mm_wp), DIMENSION(:,:), INTENT(out) :: dgazs |
---|
151 | !! Tendencies of each condensible gaz species (\(mol.mol^{-1}\)) . |
---|
152 | REAL(kind=mm_wp), DIMENSION(:,:), INTENT(out) :: gazsat |
---|
153 | !! Saturation ratio of each condensible specie. |
---|
154 | INTEGER :: i,idx,ng |
---|
155 | TYPE(mm_esp) :: xESP |
---|
156 | REAL(kind=mm_wp), DIMENSION(:,:), ALLOCATABLE :: zdm0a,zdm3a,zdm0n,zdm3n |
---|
157 | ALLOCATE(zdm0a(mm_nla,mm_nesp),zdm3a(mm_nla,mm_nesp), & |
---|
158 | zdm0n(mm_nla,mm_nesp),zdm3n(mm_nla,mm_nesp)) |
---|
159 | zdm0a(:,:) = 0._mm_wp ; zdm3a(:,:) = 0._mm_wp |
---|
160 | zdm0n(:,:) = 0._mm_wp ; zdm3n(:,:) = 0._mm_wp |
---|
161 | DO i = 1, mm_nesp |
---|
162 | call nc_esp(mm_xESPS(i),mm_gazs(:,i),mm_m3ice(:,i),dgazs(:,i),dm3i(:,i), & |
---|
163 | zdm0a(:,i),zdm3a(:,i),zdm0n(:,i),zdm3n(:,i),gazsat(:,i)) |
---|
164 | ENDDO |
---|
165 | |
---|
166 | ! Computes balance : |
---|
167 | ! Each ice components has been treated independently from the others, and |
---|
168 | ! their tendencies are returned as is (just converted in input units). |
---|
169 | ! |
---|
170 | ! Aerosols and CCN distribution evolution depends on the ice components: |
---|
171 | ! - For nucleation only creation of CCN can occur. |
---|
172 | ! - For condensation only loss of CCN can occur. |
---|
173 | ! We use the simple following rule : |
---|
174 | ! The global variation of CCN (and thus aerosols) is determined from the |
---|
175 | ! most intense activity of the ice components. |
---|
176 | ! that is the maximum value of the CCN tendencies regardless of its sign. |
---|
177 | DO i=1, mm_nla |
---|
178 | idx = MAXLOC(zdm0n(i,:),DIM=1) ! WARNING this is not the definition above (should be in ABS() func) |
---|
179 | dm0n(i) = zdm0n(i,idx) |
---|
180 | dm3n(i) = zdm3n(i,idx) |
---|
181 | dm0a(i) = zdm0a(i,idx) |
---|
182 | dm3a(i) = zdm3a(i,idx) |
---|
183 | ! all ice are returned but we must convert their units |
---|
184 | dm3i(i,:) = dm3i(i,:) |
---|
185 | ENDDO |
---|
186 | END SUBROUTINE mm_cloud_nucond |
---|
187 | |
---|
188 | SUBROUTINE nc_esp(xESP,vapX,m3iX,dvapX,dm3iX,dm0aer,dm3aer,dm0ccn,dm3ccn,Xsat) |
---|
189 | !! Get moments tendencies through nucleation/condensation/evaporation of a given condensible specie. |
---|
190 | !! |
---|
191 | !! The method computes the global tendencies of the aerosols, ccn and "ice" moments through cloud |
---|
192 | !! microphysics processes (nucleation & condensation). |
---|
193 | !! |
---|
194 | !! @warning |
---|
195 | !! Input quantities __m3iX__,__m3iO__, __m0aer__,__m3aer__, __m0ccn__,__m3ccn__ are assumed to be in |
---|
196 | !! \(X.kg^{-1}\) (where X is the unit of the moment that is, a number for M0 and a volume - \(m^3\) |
---|
197 | !! for M3) ; __vapX__ must be expressed in term of molar fraction. |
---|
198 | TYPE(mm_esp), INTENT(in) :: xESP |
---|
199 | !! Condensate specie properties. |
---|
200 | REAL(kind=mm_wp),INTENT(in), DIMENSION(:) :: vapX |
---|
201 | !! Gas specie molar fraction on the vertical grid from __TOP__ to __GROUND__ (\(mol.mol^{-1}\)). |
---|
202 | REAL(kind=mm_wp),INTENT(in), DIMENSION(:) :: m3iX |
---|
203 | !! 3rd order moment of the ice component (\(m^{3}.m^{-3}\)). |
---|
204 | REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: dvapX |
---|
205 | !! Tendency of gas specie (\(mol.mol^{-1}\)). |
---|
206 | REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: dm3iX |
---|
207 | !! Tendency of the 3rd order moment of the ice component (\(m^{3}.m^{-3}\)). |
---|
208 | REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: dm0aer |
---|
209 | !! Tendency of the 0th order moment of the fractal mode distribution (\(m^{-3}\)). |
---|
210 | REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: dm3aer |
---|
211 | !! Tendency of the 3rd order moment of the fractal mode distribution (\(m^{3}.m^{-3}\)). |
---|
212 | REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: dm0ccn |
---|
213 | !! Tendency of the 0th order moment of the ccn distribution (\(m^{-3}\)). |
---|
214 | REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: dm3ccn |
---|
215 | !! Tendency of the 3rd order moment of the ccn distribution (\(m^{3}.m^{-3}\)). |
---|
216 | REAL(kind=mm_wp),INTENT(out), DIMENSION(:) :: Xsat |
---|
217 | !! Saturation ratio values on the vertical grid (--). |
---|
218 | INTEGER :: i |
---|
219 | REAL(kind=mm_wp) :: bef,aft |
---|
220 | REAL(kind=mm_wp), DIMENSION(SIZE(vapX)) :: sm0a,sm3a,sm0n,sm3n,sm3iX |
---|
221 | REAL(kind=mm_wp), DIMENSION(SIZE(vapX)) :: zm0a,zm3a,zm0n,zm3n,zm3iX,zvapX |
---|
222 | REAL(kind=mm_wp), DIMENSION(SIZE(vapX)) :: pX,sig,qsat,lheat,seq,up,down, & |
---|
223 | ctot,newvap,nucr,grate,cm0,cm3 |
---|
224 | ! Initialization : |
---|
225 | ! Copy input argument and convert units X.m-3 -> X.kg-1) |
---|
226 | ! sXXX is the initial converted value saved |
---|
227 | sm3iX = m3iX/mm_rhoair |
---|
228 | sm0a = mm_m0aer_f/mm_rhoair ; sm3a = mm_m3aer_f/mm_rhoair |
---|
229 | sm0n = mm_m0ccn/mm_rhoair ; sm3n = mm_m3ccn/mm_rhoair |
---|
230 | ! zXXX is our working copy |
---|
231 | zm3ix = sm3ix ; zm0a = sm0a ; zm3a = sm3a ; zm0n = sm0n ; zm3n = sm3n |
---|
232 | |
---|
233 | ! Molar fraction of X specie is set in mass mixing ratio |
---|
234 | zvapX = vapX * xESP%fmol2fmas |
---|
235 | ! Surface tension |
---|
236 | sig = mm_sigX(mm_temp,xESP) |
---|
237 | ! X specie mass mixing ratio at saturation |
---|
238 | qsat = mm_qsatX(mm_temp,mm_play,xESP) |
---|
239 | ! partial pressure of X specie |
---|
240 | pX = vapX * mm_play |
---|
241 | ! Saturation ratio |
---|
242 | Xsat = zvapX / qsat |
---|
243 | ! Equilibrium saturation near the drop |
---|
244 | seq = dexp(2._mm_wp*sig*xESP%masmol/(xESP%rho*mm_rgas*mm_temp*mm_drad)) |
---|
245 | ! Latent heat released |
---|
246 | lheat = mm_lheatX(mm_temp,xESP) |
---|
247 | ! Gets nucleation rate (ccn radius is the monomer !) |
---|
248 | call nuc_rate((/(mm_rm, i=1,mm_nla)/),mm_temp,xESP,pX,Xsat,nucr) |
---|
249 | ! Gets growth rate |
---|
250 | call growth_rate(mm_temp,mm_play,pX/Xsat,xESP,seq,mm_drad,grate) |
---|
251 | ctot = zvapx + xESP%rho * m3iX |
---|
252 | up = vapx + mm_dt * grate * 4._mm_wp * mm_pi * xESP%rho * mm_drad * seq * zm0n |
---|
253 | down = 1._mm_wp + mm_dt * grate * 4._mm_wp * mm_pi * xESP%rho * mm_drad / qsat * zm0n |
---|
254 | ! gets new vapor X specie mass mixing ratio : cannot be greater than the |
---|
255 | ! total gas + ice and lower than nothing :) |
---|
256 | newvap = max(min(up/down,ctot),0._mm_wp) |
---|
257 | ! gets "true" growth rate |
---|
258 | grate = grate * (newvap/qsat - seq) |
---|
259 | |
---|
260 | ! computes tendencies through condensation |
---|
261 | ! 1) check for the specific case : NO ICE and SUBLIMATION |
---|
262 | WHERE (zm3iX <= 0._mm_wp .AND. grate <= 0._mm_wp) |
---|
263 | ! no ice and sublimation : reset ice to 0 |
---|
264 | zm3iX = 0._mm_wp |
---|
265 | ELSEWHERE |
---|
266 | ! update ice volume ... |
---|
267 | zm3iX = zm3iX + mm_dt*grate*4._mm_wp*mm_pi*mm_drad*zm0n |
---|
268 | ! ... and check if there ice left in the ccn |
---|
269 | WHERE (zm3ix <= 0._mm_wp) |
---|
270 | zm3ix = 0._mm_wp |
---|
271 | zm0a = zm0a + zm0n ; zm0n = 0._mm_wp |
---|
272 | zm3a = zm3a + zm3n ; zm3n = 0._mm_wp |
---|
273 | ENDWHERE |
---|
274 | ENDWHERE |
---|
275 | |
---|
276 | ! computes tendencies |
---|
277 | ! all of these tendencies are in X.kg-1 |
---|
278 | dm0aer = zm0a - sm0a |
---|
279 | dm3aer = zm3a - sm3a |
---|
280 | dm0ccn = zm0n - sm0n |
---|
281 | dm3ccn = zm3n - sm3n |
---|
282 | dm3ix = zm3ix - sm3ix |
---|
283 | ! and this one is in mol.mol-1 |
---|
284 | dvapx = -xESP%rho * dm3ix / xESP%fmol2fmas |
---|
285 | |
---|
286 | ! reset temporary arrays to initial values |
---|
287 | zm3ix = sm3ix ; zm0a = sm0a ; zm3a = sm3a ; zm0n = sm0n ; zm3n = sm3n |
---|
288 | |
---|
289 | ! Computes global tendencies (nucleation && condensation) |
---|
290 | ! |
---|
291 | ! for nucleation we have the following equations: |
---|
292 | ! dMaer_(k)/dt = - dMccn_(k)/dt (conservation of aerosols+ccn) (1) |
---|
293 | ! dMaer_(k)/dt = - 4*PI*nucr/rm * Maer_(k+3) (2) |
---|
294 | ! = - 4*PI*nucr/rm * alpha(k+3)/alpha(k) * Maer_(k) |
---|
295 | ! where alpha(k+3) = Maer_(k+3)/Maer_(0) / rc**(k+3) |
---|
296 | ! We solve (implicit scheme) : |
---|
297 | ! CONST_M(k) = 4*PI*nucr/rm * alpha(k+3)/alpha(k)*rc**3 * dt |
---|
298 | ! Maer_(k)[t+dt] = 1/(1+CONST_M(k)) * Maer_(k)[t] (3) |
---|
299 | ! Then, from eq. 2: |
---|
300 | ! Mccn_(k)[t+dt] = Mccn_(k)[t] + CONST_M(k)/(1+CONST_M(k))*Maer_(k)[t] (4) |
---|
301 | ! |
---|
302 | cm0 = 4._mm_wp*mm_pi*nucr/mm_rm*mm_alpha_f(3._mm_wp)*mm_rcf**3*mm_dt |
---|
303 | cm3 = 4._mm_wp*mm_pi*nucr/mm_rm*mm_alpha_f(6._mm_wp)/mm_alpha_f(3._mm_wp)*mm_rcf**3*mm_dt |
---|
304 | zm0a = 1._mm_wp/(1._mm_wp+cm0) * zm0a |
---|
305 | zm3a = 1._mm_wp/(1._mm_wp+cm0) * zm3a |
---|
306 | WHERE (zm0a <= 0._mm_wp .OR. zm3a <= 0._mm_wp) |
---|
307 | zm0a=0._mm_wp |
---|
308 | zm3a=0._mm_wp |
---|
309 | zm0n = zm0n + sm0a |
---|
310 | zm3n = zm3n + sm3a |
---|
311 | ELSEWHERE |
---|
312 | zm0n = zm0n + cm0/(1.+cm0)*zm0a |
---|
313 | zm3n = zm3n + cm3/(1.+cm3)*zm3a |
---|
314 | ENDWHERE |
---|
315 | |
---|
316 | ! Adds condensation tendencies |
---|
317 | zm0a = zm0a + dm0aer |
---|
318 | zm3a = zm3a + dm3aer |
---|
319 | zm0n = zm0n + dm0ccn |
---|
320 | zm3n = zm3n + dm3ccn |
---|
321 | |
---|
322 | ! Computes balance |
---|
323 | IF (mm_debug) THEN |
---|
324 | WRITE(*,'(a)') "Condensation/nucleation balance :" |
---|
325 | DO i=1,mm_nla |
---|
326 | bef = sm0a(i) + sm0n(i) |
---|
327 | aft = zm0a(i) + zm0n(i) |
---|
328 | IF (ABS(bef-aft)/bef > 1e-10_mm_wp) WRITE(*,'((a),I2.2,(a))') & |
---|
329 | "[WARNING] nc_esp speaking: Total number not conserved (z=",i,")" |
---|
330 | bef = sm3a(i) + sm3n(i) |
---|
331 | aft = zm3a(i) + zm3n(i) |
---|
332 | IF (ABS(bef-aft)/bef > 1e-10_mm_wp) WRITE(*,'((a),I2.2,(a))') & |
---|
333 | "[WARNING] nc_esp speaking: Total volume not conserved (z=",i,")" |
---|
334 | ENDDO |
---|
335 | ENDIF |
---|
336 | |
---|
337 | ! Now updates tendencies |
---|
338 | dm0aer = (zm0a-sm0a)*mm_rhoair |
---|
339 | dm3aer = (zm3a-sm3a)*mm_rhoair |
---|
340 | dm0ccn = (zm0n-sm0n)*mm_rhoair |
---|
341 | dm3ccn = (zm3n-sm3n)*mm_rhoair |
---|
342 | |
---|
343 | END SUBROUTINE nc_esp |
---|
344 | |
---|
345 | SUBROUTINE nuc_rate(rccn,temp,xESP,pvp,sat,rate) |
---|
346 | !! Get nucleation rate. |
---|
347 | !! |
---|
348 | !! The method computes the heterogeneous nucleation rate for the given specie on a fractal particle |
---|
349 | !! of size __rccn__. |
---|
350 | !! Except __xESP__, all arguments are vectors of the same size (vertical grid). |
---|
351 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: rccn !! Radius of the cloud condensation nuclei (m). |
---|
352 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: temp !! Temperature (K). |
---|
353 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: pvp !! Partial vapor pressure of X specie (Pa). |
---|
354 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: sat !! Saturation ratio of given specie (--). |
---|
355 | TYPE(mm_esp), INTENT(in) :: xESP !! X specie properties (--). |
---|
356 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: rate !! The nucleation rate (\(m^-{2}.s^{-1}\)). |
---|
357 | INTEGER :: nv |
---|
358 | REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: nX,rstar,gstar,x,zeldov,deltaf, & |
---|
359 | fsh,fstar,sig |
---|
360 | nv = SIZE(rccn) |
---|
361 | ALLOCATE(nX(nv), rstar(nv), gstar(nv), x(nv), zeldov(nv), & |
---|
362 | deltaf(nv), fsh(nv), fstar(nv)) |
---|
363 | ! Activation condition |
---|
364 | WHERE (sat > 1._mm_wp) |
---|
365 | sig = mm_sigX(temp,xESP) |
---|
366 | nX = pvp/mm_kboltz/temp |
---|
367 | rstar = 2._mm_wp*sig*xESP%vol/(mm_kboltz*temp*dlog(sat)) |
---|
368 | ! curvature radius |
---|
369 | x = rccn/rstar |
---|
370 | fsh = mm_fshape(xESP%mteta,x) |
---|
371 | fstar = (4._mm_wp/3._mm_wp*mm_pi)*sig*(rstar**2.)*fsh |
---|
372 | deltaf=MIN(MAX((2.*mm_fdes-mm_fdif-fstar)/(mm_kboltz*temp),-100._mm_wp),100._mm_wp) |
---|
373 | WHERE (deltaf == -100._mm_wp) |
---|
374 | rate = 0._mm_wp |
---|
375 | ELSEWHERE |
---|
376 | gstar = 4._mm_wp*mm_pi*(rstar**3)/(3._mm_wp*xESP%vol) |
---|
377 | zeldov = dsqrt(fstar/(3._mm_wp*mm_pi*mm_kboltz*temp*(gstar**2))) |
---|
378 | rate = zeldov*mm_kboltz*temp*(nX*rstar)**2._mm_wp*dexp(deltaf)/ & |
---|
379 | (fsh*mm_nus*xESP%mas) |
---|
380 | ENDWHERE |
---|
381 | ELSEWHERE |
---|
382 | rate = 0._mm_wp |
---|
383 | ENDWHERE |
---|
384 | DEALLOCATE(nX,rstar,gstar,x,zeldov,deltaf,fsh,fstar) |
---|
385 | RETURN |
---|
386 | END SUBROUTINE nuc_rate |
---|
387 | |
---|
388 | SUBROUTINE growth_rate(temp,pres,pXsat,xESP,seq,drad,rate) |
---|
389 | !! Get growth rate through condensation/evaporation process. |
---|
390 | !! |
---|
391 | !! The method computes the growth rate a drop through condensation/evaporation processes: |
---|
392 | !! |
---|
393 | !! $$ r \times \frac{dr}{dt} = g_{rate} \times (S - S_{eq}) $$ |
---|
394 | !! |
---|
395 | !! Except __xESP__ which is a scalar, all arguments are vectors of the same size (vertical grid). |
---|
396 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: temp !! Temperature (K). |
---|
397 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: pres !! Pressure level (Pa). |
---|
398 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: seq !! Saturation vapor pressure of specie (Pa). |
---|
399 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: drad !! Specie properties. |
---|
400 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: pXsat !! Equilibrium saturation near the drop. |
---|
401 | TYPE(mm_esp), INTENT(in) :: xESP !! Drop radius (m). |
---|
402 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: rate !! Growth rate (\(m^{2}.s^{-1}\)). |
---|
403 | REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: k,knu,slf,rkc,rdc,l,dv |
---|
404 | INTEGER :: n |
---|
405 | n = SIZE(temp) |
---|
406 | ALLOCATE(k(n),knu(n),slf(n),rkc(n),rdc(n),l(n),dv(n)) |
---|
407 | |
---|
408 | ! N2 (air) Thermal conductivity (where does it come from ?) |
---|
409 | k(:) = ( 2.857e-2_mm_wp*temp-0.5428_mm_wp)*4.184e-3_mm_wp |
---|
410 | ! Gas mean free path |
---|
411 | l(:) = mm_lambda_g(temp,pres) |
---|
412 | ! Diffusion coefficient of X gas |
---|
413 | Dv(:) = 1._mm_wp/3._mm_wp*dsqrt(8._mm_wp*mm_rgas*temp(:)/(mm_pi*xESP%masmol))*mm_kboltz*temp(:) / & |
---|
414 | (mm_pi*pres(:)*(mm_air_rad+xESP%ray)**2* dsqrt(1._mm_wp+xESP%fmol2fmas)) |
---|
415 | knu(:) = l(:)/drad(:) ! The knudsen number of the drop |
---|
416 | slf(:) = (1.333_mm_wp+0.71_mm_wp/knu(:))/(1._mm_wp+1._mm_wp/knu(:)) ! Slip flow correction |
---|
417 | Dv(:) = Dv(:)/(1._mm_wp+slf(:)*knu(:)) |
---|
418 | ! latent heat resistance coefficient |
---|
419 | rkc(:) = mm_lheatX(temp(:),xESP)**2 * xESP%rho * xESP%masmol / (k(:)*mm_rgas*temp(:)**2) |
---|
420 | ! Diffusion resistance coefficient |
---|
421 | rdc(:) = mm_rgas * temp(:) * xESP%rho / (Dv(:)*pXsat(:)*xESP%masmol) |
---|
422 | ! Growth rate: rdr/dt = rate * (S-Seq) ; rate is returned |
---|
423 | rate(:) = 1._mm_wp / (seq(:)*rkc(:)+rdc(:)) |
---|
424 | RETURN |
---|
425 | END SUBROUTINE growth_rate |
---|
426 | |
---|
427 | |
---|
428 | !----------------------------------------------------------------------------- |
---|
429 | ! SEDIMENTATION PROCESS RELATED METHODS |
---|
430 | !----------------------------------------------------------------------------- |
---|
431 | |
---|
432 | SUBROUTINE mm_cloud_sedimentation(dm0n,dm3n,dm3i) |
---|
433 | !! Compute the tendency of _clouds_ related moments through sedimentation process. |
---|
434 | !! |
---|
435 | !! The method computes the tendencies of moments related to cloud microphysics through |
---|
436 | !! sedimentation process. The algorithm used here differs from |
---|
437 | !! [[mm_haze(module):mm_haze_sedimentation(subroutine)]] as all moments settle with the same |
---|
438 | !! terminal velocity which is computed with the average drop radius of the size distribution. |
---|
439 | !! We simply compute an _exchange matrix_ that stores the new positions of each cells through |
---|
440 | !! sedimentation process and then computes the matrix |
---|
441 | !! product with input moments values to get final tendencies. |
---|
442 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm0n |
---|
443 | !! Tendency of the 0th order moment of the ccn distribution (\(m^{-3}\)). |
---|
444 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm3n |
---|
445 | !! Tendency of the 3rd order moment of the ccn distribution (\(m^{3}.m^{-3}\)). |
---|
446 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:,:) :: dm3i |
---|
447 | !! Tendencies of the 3rd order moment of each ice component of the cloud (\(m^{3}m^{-3}\)). |
---|
448 | INTEGER :: im,nm |
---|
449 | REAL(kind=mm_wp), DIMENSION(:,:), ALLOCATABLE :: moms, momsf,chg_matrix |
---|
450 | nm = 2 + mm_nesp |
---|
451 | ALLOCATE(moms(mm_nla,nm),momsf(mm_nla,nm),chg_matrix(mm_nla,mm_nla)) |
---|
452 | ! Initializes moms |
---|
453 | moms(:,1) = mm_m0ccn * mm_dzlev |
---|
454 | moms(:,2) = mm_m3ccn * mm_dzlev |
---|
455 | DO im=1,mm_nesp |
---|
456 | moms(:,2+im) = mm_m3ice(:,im) * mm_dzlev |
---|
457 | ENDDO |
---|
458 | ! Computes exchange matrix |
---|
459 | CALL exchange(mm_drad,mm_drho,mm_dt,chg_matrix) |
---|
460 | ! Computes final moments values |
---|
461 | DO im=1,nm ; momsf(:,im) = MATMUL(chg_matrix,moms(:,im)) ; ENDDO |
---|
462 | ! Computes tendencies (converted in X.m-3) |
---|
463 | dm0n = (momsf(:,1)-moms(:,1))/mm_dzlev |
---|
464 | dm3n = (momsf(:,2)-moms(:,2))/mm_dzlev |
---|
465 | DO im=1,mm_nesp |
---|
466 | dm3i(:,im) = (momsf(:,2+im)-moms(:,2+im))/mm_dzlev |
---|
467 | ENDDO |
---|
468 | RETURN |
---|
469 | END SUBROUTINE mm_cloud_sedimentation |
---|
470 | |
---|
471 | SUBROUTINE exchange(rad,rhog,dt,matrix) |
---|
472 | !! Compute the exchange matrix. |
---|
473 | !! |
---|
474 | !! The subroutine computes the matrix exchange used by |
---|
475 | !! [[mm_clouds(module):mm_cloud_sedimentation(subroutine)]] to compute moments tendencies |
---|
476 | !! through sedimentation process. Both __rad__ and __rhog__ must be vector with relevant |
---|
477 | !! values over the atmospheric vertical structure. __matrix__ is square 2D-array with same |
---|
478 | !! dimension size than __rad__. |
---|
479 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: rad |
---|
480 | !! Cloud drop radius over the atmospheric vertical structure (m). |
---|
481 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: rhog |
---|
482 | !! Cloud drop density over the atmospheric vertical structure (\(kg.m^{-3}\)). |
---|
483 | REAL(kind=mm_wp), INTENT(in) :: dt |
---|
484 | !! Timestep (s). |
---|
485 | REAL(kind=mm_wp), INTENT(out) :: matrix(:,:) |
---|
486 | !! The output _exchange matrix_. |
---|
487 | INTEGER :: nz,i,j,jj,jinf,jsup |
---|
488 | REAL(kind=mm_wp) :: zni,znip1,xf,xft,xcnt |
---|
489 | REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: puit |
---|
490 | REAL(kind=mm_wp) :: cpte,cpte2 |
---|
491 | INTEGER, PARAMETER :: ichx = 1 |
---|
492 | matrix = 0._mm_wp ; nz = SIZE(rad) ; ALLOCATE(puit(nz)) |
---|
493 | ! compute exchange matrix |
---|
494 | DO i=1,nz |
---|
495 | puit(i) = 0._mm_wp |
---|
496 | xcnt = 0._mm_wp |
---|
497 | ! computes drop move (i.e. its new positions) |
---|
498 | CALL getnzs(ichx,i,rad,rhog,dt,zni,znip1) |
---|
499 | |
---|
500 | ! Peculiar case : Ground level precipitation [znip1<0 && (zni<0 || zni>0)] |
---|
501 | ! Complete precipitation [ znip1 <= 0 && zni <= 0 ] : |
---|
502 | IF(zni<=0._mm_wp.and.znip1<=0._mm_wp) THEN |
---|
503 | xft=0._mm_wp |
---|
504 | xf=1._mm_wp |
---|
505 | xcnt=xcnt+xf |
---|
506 | puit(i)=puit(i)+xf |
---|
507 | ENDIF |
---|
508 | ! partial precipitation [ znip1 <= 0 && zni > 0 ] : |
---|
509 | IF (zni>0._mm_wp .and. znip1 <= 0._mm_wp) THEN |
---|
510 | xft=zni/(zni-znip1) |
---|
511 | xf=(1.-xft) |
---|
512 | xcnt=xcnt+xf |
---|
513 | puit(i)=puit(i)+xf |
---|
514 | ENDIF |
---|
515 | ! General case: no ground precipitation [ znip1 > 0 && zni > 0 ] |
---|
516 | IF (zni>0._mm_wp.and.znip1>0._mm_wp) THEN |
---|
517 | xft = 1._mm_wp ! on a la totalite de la case |
---|
518 | xf = 0._mm_wp |
---|
519 | xcnt=xcnt+xf |
---|
520 | puit(i)=puit(i)+xf |
---|
521 | ENDIF |
---|
522 | ! Fix minimum level to the ground |
---|
523 | znip1 = MAX(znip1,0.) |
---|
524 | zni = MAX(zni,0.) |
---|
525 | ! Locate new "drop" position in the verical grid |
---|
526 | jsup=nz+1 |
---|
527 | jinf=nz+1 |
---|
528 | DO j=1,nz |
---|
529 | IF (zni<=mm_zlev(j).and.zni>=mm_zlev(j+1)) jsup=j |
---|
530 | IF (znip1<=mm_zlev(j).and.znip1>=mm_zlev(j+1)) jinf=j |
---|
531 | ENDDO |
---|
532 | ! Volume is out of range: (all drops have touched the ground!) |
---|
533 | ! Note: can happen here,it has been treated previously :) |
---|
534 | IF (jsup>=nz+1.and.jinf==jsup) THEN |
---|
535 | WRITE(*,'(a)') "[EXCHANGE] speaking: The impossible happened !" |
---|
536 | call EXIT(666) |
---|
537 | ENDIF |
---|
538 | ! Volume inside a single level |
---|
539 | IF (jsup==jinf.and.jsup<=nz) THEN |
---|
540 | xf=1._mm_wp |
---|
541 | xcnt=xcnt+xft*xf |
---|
542 | matrix(jinf,i)=matrix(jinf,i)+xft*xf |
---|
543 | ENDIF |
---|
544 | |
---|
545 | ! Volume over 2 levels |
---|
546 | IF (jinf==jsup+1) THEN |
---|
547 | xf=(zni-mm_zlev(jinf))/(zni-znip1) |
---|
548 | xcnt=xcnt+xf*xft |
---|
549 | IF(jsup<=nz) THEN |
---|
550 | matrix(jsup,i)=matrix(jsup,i)+xft*xf |
---|
551 | ENDIF |
---|
552 | xf=(mm_zlev(jinf)-znip1)/(zni-znip1) |
---|
553 | xcnt=xcnt+xf*xft |
---|
554 | IF (jinf<=nz) THEN |
---|
555 | matrix(jinf,i)=matrix(jinf,i)+xft*xf |
---|
556 | ENDIF |
---|
557 | ENDIF |
---|
558 | |
---|
559 | ! Volume over 3 or more levels |
---|
560 | IF (jinf > jsup+1) THEN |
---|
561 | ! first cell |
---|
562 | xf=(zni-mm_zlev(jsup+1))/(zni-znip1) |
---|
563 | xcnt=xcnt+xf*xft |
---|
564 | matrix(jsup,i)=matrix(jsup,i)+xft*xf |
---|
565 | ! last cell |
---|
566 | xf=(mm_zlev(jinf)-znip1)/(zni-znip1) |
---|
567 | xcnt=xcnt+xf*xft |
---|
568 | matrix(jinf,i)=matrix(jinf,i)+xft*xf |
---|
569 | ! other :) |
---|
570 | DO jj=jsup+1,jinf-1 |
---|
571 | xf=(mm_zlev(jj)-mm_zlev(jj+1))/(zni-znip1) |
---|
572 | xcnt=xcnt+xf*xft |
---|
573 | matrix(jj,i)=matrix(jj,i)+xft*xf |
---|
574 | ENDDO |
---|
575 | ENDIF |
---|
576 | ENDDO |
---|
577 | ! checking if everything is alright if debug enabled... |
---|
578 | IF (mm_debug) THEN |
---|
579 | cpte=0._mm_wp ; cpte2=0._mm_wp |
---|
580 | DO j=1,nz |
---|
581 | DO jj=1,nz |
---|
582 | cpte=cpte+matrix(jj,j) |
---|
583 | ENDDO |
---|
584 | cpte2=cpte+puit(j) |
---|
585 | ENDDO |
---|
586 | IF (abs(cpte2-nz)>1.e-4_mm_wp) THEN |
---|
587 | WRITE(*,'(a)')"[EXCHANGE] speaking :" |
---|
588 | WRITE(*,'("tx expl (/nz):",2(2X,ES10.3))') cpte,cpte2 |
---|
589 | ENDIF |
---|
590 | ENDIF |
---|
591 | RETURN |
---|
592 | END SUBROUTINE exchange |
---|
593 | |
---|
594 | SUBROUTINE getnzs(ichx,idx,rad,rho,dt,zni,zns) |
---|
595 | !! Compute displacement of a cell under sedimentation process. |
---|
596 | !! |
---|
597 | !! The method computes the new position of a _drop cell_ through sedimentation process as |
---|
598 | !! descibed in the following scheme: |
---|
599 | !! |
---|
600 | !! ![Cloud sedimentation scheme](|media|/cloud_sed_scheme.svg) |
---|
601 | !! |
---|
602 | !! New positions are returned in __zni__ and __zns__ ouptut arguments. |
---|
603 | !! |
---|
604 | !! @note |
---|
605 | !! The method uses directly [[mm_globals(module):mm_play(variable)]], [[mm_globals(module):mm_plev(variable)]], |
---|
606 | !! [[mm_globals(module):mm_temp(variable)]],[[mm_globals(module):mm_btemp(variable)]], |
---|
607 | !! [[mm_globals(module):mm_zlay(variable)]] and [[mm_globals(module):mm_zlev(variable)]] and uses __idx__ to |
---|
608 | !! get the relevant value to use on the vertical grid. |
---|
609 | INTEGER, INTENT(in) :: ichx |
---|
610 | !! Velocity extrapolation control flag (0 for linear, 1 for exponential -preferred -). |
---|
611 | INTEGER, INTENT(in) :: idx |
---|
612 | !! Initial position of the drop (subscript of vertical layers vectors). |
---|
613 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: rad |
---|
614 | !! Cloud drop radius over the atmospheric vertical structure (m). |
---|
615 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: rho |
---|
616 | !! Cloud drop density over the atmospheric vertical structure (\(kg.m^{-3}\)). |
---|
617 | REAL(kind=mm_wp), INTENT(in) :: dt |
---|
618 | !! Timestep (s). |
---|
619 | REAL(kind=mm_wp), INTENT(out) :: zni |
---|
620 | !! Final layer center position (m). |
---|
621 | REAL(kind=mm_wp), INTENT(out) :: zns |
---|
622 | !! Final layer upper boundary position (m). |
---|
623 | REAL(kind=mm_wp) :: ws,wi,w,zi,zs |
---|
624 | REAL(kind=mm_wp) :: alpha,argexp,v0,arg1,arg2 |
---|
625 | INTEGER :: i,nz |
---|
626 | REAL(kind=mm_wp), PARAMETER :: es = 30._mm_wp |
---|
627 | nz = SIZE(rad) |
---|
628 | ! Linear extrapolation of velocity |
---|
629 | IF (ichx==0) THEN |
---|
630 | ! velocity upper interface |
---|
631 | ws = wsettle(mm_plev(idx),mm_btemp(idx),mm_zlev(idx),rho(idx),rad(idx)) |
---|
632 | IF (idx==nz) THEN |
---|
633 | ! veloctity center layer |
---|
634 | wi = wsettle(mm_play(idx),mm_temp(idx),mm_zlay(idx),rho(idx),rad(idx)) |
---|
635 | ELSEIF(idx<nz) THEN |
---|
636 | ! velocity lower interface |
---|
637 | wi = wsettle(mm_plev(idx+1),mm_btemp(idx+1),mm_zlev(idx+1), & |
---|
638 | rho(idx+1),rad(idx+1)) |
---|
639 | ELSE |
---|
640 | WRITE(*,'(a)') "[getnzs] speaking:" |
---|
641 | WRITE(*,'(a)') "This is the fatal error..." |
---|
642 | WRITE(*,'(a)') "index is higher than number of levels" |
---|
643 | call EXIT(111) |
---|
644 | ENDIF |
---|
645 | w = (ws+wi)/2._mm_wp |
---|
646 | zni = mm_zlev(idx)-w*dt |
---|
647 | zns = mm_zlev(idx)-mm_dzlev(idx)-w*dt |
---|
648 | RETURN |
---|
649 | ! Exponential extrapolation of velocity |
---|
650 | ELSEIF(ichx==1) THEN |
---|
651 | ws = wsettle(mm_plev(idx),mm_btemp(idx),mm_zlev(idx),rho(idx),rad(idx)) |
---|
652 | zs = mm_zlev(idx) |
---|
653 | wi = wsettle(mm_play(idx),mm_temp(idx),mm_zlay(idx),rho(idx),rad(idx)) |
---|
654 | zi=mm_zlay(idx) |
---|
655 | ! ws & wi must be different ! |
---|
656 | IF(dabs(wi-ws)/wi <= 1.e-3_mm_wp) wi=ws/1.001_mm_wp |
---|
657 | IF (wi /= 0._mm_wp) alpha = dlog(ws/wi)/(zs-zi) ! alpha < 0 if wi > ws |
---|
658 | ! -es < argexp < es |
---|
659 | argexp=MAX(MIN(alpha*zs,es),-es) |
---|
660 | v0 = ws/dexp(argexp) |
---|
661 | arg1=1._mm_wp+v0*alpha*dexp(argexp)*dt |
---|
662 | argexp=MAX(MIN(alpha*(mm_zlev(idx)-mm_dzlev(idx)),es),-es) |
---|
663 | arg2=1._mm_wp+v0*alpha*dexp(argexp)*dt |
---|
664 | IF (arg1<=0._mm_wp.OR.arg2<=0._mm_wp) THEN |
---|
665 | ! correct velocity |
---|
666 | ! divides the velocity argument in arg1 and arg2 : |
---|
667 | ! argX=1+alpha*v0*exp(alpha*z)*dt <==> argX-1=alpha*v0*exp(alpha*z)*dt |
---|
668 | ! ==> argX' = 1 + (argX-1)/2 <==> argX' = (1+argX)/2. |
---|
669 | DO i=1,25 |
---|
670 | IF (arg1<=0._mm_wp.OR.arg2<=0._mm_wp) THEN |
---|
671 | IF (mm_debug) & |
---|
672 | WRITE(*,'((a),I2.2,(a))') "[getnzs] must adjust velocity (",i,"/25)" |
---|
673 | arg1=(arg1+1._mm_wp)/2._mm_wp ; arg2=(arg2+1._mm_wp)/2._mm_wp |
---|
674 | ELSE |
---|
675 | EXIT |
---|
676 | ENDIF |
---|
677 | ENDDO |
---|
678 | ! sh** we have to stop |
---|
679 | IF (i>25) THEN |
---|
680 | WRITE(*,'(a)')"[getnzs] speaking:" |
---|
681 | WRITE(*,'(a)') "Cannot adjust velocities" |
---|
682 | call EXIT(111) |
---|
683 | ENDIF |
---|
684 | ENDIF |
---|
685 | zni = mm_zlev(idx)-dlog(arg1)/alpha |
---|
686 | zns = mm_zlev(idx)-mm_dzlev(idx)-dlog(arg2)/alpha |
---|
687 | RETURN |
---|
688 | ENDIF |
---|
689 | END SUBROUTINE getnzs |
---|
690 | |
---|
691 | ELEMENTAL FUNCTION wsettle(p,t,z,rho,rad) RESULT(w) |
---|
692 | !! Compute the settling velocity of a spherical particle. |
---|
693 | !! |
---|
694 | !! The method computes the effective settling velocity of spherical particle of |
---|
695 | !! radius __rad__. It accounts for the slip-flow transition (no approximation). |
---|
696 | REAL(kind=mm_wp), INTENT(in) :: p !! The pressure level (Pa). |
---|
697 | REAL(kind=mm_wp), INTENT(in) :: t !! The temperature (K). |
---|
698 | REAL(kind=mm_wp), INTENT(in) :: z !! The altitude level (m). |
---|
699 | REAL(kind=mm_wp), INTENT(in) :: rho !! Density of the particle (\(kg.m^{-3}\)). |
---|
700 | REAL(kind=mm_wp), INTENT(in) :: rad !! Radius of the particle (m). |
---|
701 | REAL(kind=mm_wp) :: w !! Settling velocity (\(m.s^{-1}\)). |
---|
702 | REAL(kind=mm_wp) :: g,a,kn,nu |
---|
703 | REAL(kind=mm_wp), PARAMETER :: ra = 1.75e-10_mm_wp, nu0 = 1.74e-4_mm_wp, c = 109._mm_wp |
---|
704 | ! Computes corrected gravity |
---|
705 | g = mm_effg(z) |
---|
706 | ! Knudsen number |
---|
707 | kn = mm_kboltz*t/(p*4._mm_wp*sqrt(2._mm_wp)*mm_pi*ra**2)/rad |
---|
708 | ! Air viscosity |
---|
709 | nu=nu0*sqrt(t/293._mm_wp)*(1._mm_wp+c/293._mm_wp)/(1._mm_wp+c/t) |
---|
710 | ! Computes settling velocity |
---|
711 | w = 2._mm_wp/9._mm_wp * rad**2*g*rho/nu |
---|
712 | ! apply slip-flow correction |
---|
713 | w = w*(1._mm_wp+1.2517_mm_wp*kn+0.4_mm_wp*kn*dexp(-1.1_mm_wp/kn)) |
---|
714 | END FUNCTION wsettle |
---|
715 | |
---|
716 | FUNCTION get_mass_flux(rho,m3) RESULT(flx) |
---|
717 | !> Get the mass flux of (clouds related) moment through sedimention. |
---|
718 | !! |
---|
719 | !! @warning |
---|
720 | !! The method is __only__ valid for cloud moments (i.e. ice or ccn). It calls |
---|
721 | !! [[mm_clouds(module):wsettle(function)]] that compute the _mean_ settling velocity of a |
---|
722 | !! cloud drop. |
---|
723 | !! |
---|
724 | !! @note |
---|
725 | !! The computed flux is always positive. |
---|
726 | REAL(kind=mm_wp), INTENT(in) :: rho |
---|
727 | !! Tracer density (\(kg.m^{-3}\)). |
---|
728 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: m3 |
---|
729 | !! Vertical profile of the total volume of tracer (i.e. M3) from __TOP__ to __GROUND__ (\(m^{3}.m^{-3}\)). |
---|
730 | REAL(kind=mm_wp), DIMENSION(SIZE(m3)) :: flx |
---|
731 | !! Mass sedimentation fluxes at each layer from __TOP__ to __GROUND__ (\(kg.m^{-2}.s^{-1}\)). |
---|
732 | REAL(kind=mm_wp), SAVE :: fac = 4._mm_wp/3._mm_wp * mm_pi |
---|
733 | flx = fac * rho * m3 * wsettle(mm_play,mm_temp,mm_zlay,mm_drho,mm_drad) |
---|
734 | RETURN |
---|
735 | END FUNCTION get_mass_flux |
---|
736 | |
---|
737 | END MODULE MM_CLOUDS |
---|