[1897] | 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 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 |
---|
| 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 license and that you accept its terms. |
---|
| 33 | |
---|
| 34 | !! file: mmp_moments.f90 |
---|
| 35 | !! summary: YAMMS/MP2M model external methods |
---|
| 36 | !! author: J. Burgalat |
---|
| 37 | !! date: 2013-2015,2017 |
---|
| 38 | !! |
---|
| 39 | !! This file contains the definitions of all external methods that should be defined |
---|
| 40 | !! for mp2m library. |
---|
| 41 | !! |
---|
| 42 | !! All the methods defined here satisify the interfaces defined in __m_interfaces__ module |
---|
| 43 | !! of YAMMS library. |
---|
| 44 | |
---|
| 45 | PURE FUNCTION mm_alpha_s(k) RESULT (res) |
---|
| 46 | !! Inter-moment relation for spherical aerosols size distribution law. |
---|
| 47 | !! |
---|
| 48 | !! The method computes the relation between the kth order moment and the 0th |
---|
| 49 | !! order moment of the size-distribution law: |
---|
| 50 | !! |
---|
| 51 | !! $$ \dfrac{M_{k}}{M_{0}} = r_{C}^{k} \times \alpha(k,a_{1},...a_{n}) $$ |
---|
| 52 | !! |
---|
| 53 | !! Here, alpha is computed as a sum of expenontial functions. |
---|
| 54 | USE MMP_GCM, ONLY : mmp_asp, mm_wp |
---|
| 55 | IMPLICIT NONE |
---|
| 56 | REAL(kind=mm_wp), INTENT(in) :: k !! k Order of the moment. |
---|
| 57 | REAL(kind=mm_wp) :: res !! Alpha value. |
---|
| 58 | res = SUM(dexp(mmp_asp%a*k**2+mmp_asp%b*k+mmp_asp%c)) |
---|
| 59 | RETURN |
---|
| 60 | END FUNCTION mm_alpha_s |
---|
| 61 | |
---|
| 62 | PURE FUNCTION mm_alpha_f(k) RESULT (res) |
---|
| 63 | !! Inter-moment relation for fractal aerosols size distribution law. |
---|
| 64 | !! |
---|
| 65 | !! [[mm_alpha_f(function)]] performs the same computations as [[mm_alpha_s(function)]] |
---|
| 66 | !! using another set of parameters for the exponential functions. |
---|
| 67 | USE MMP_GCM, ONLY : mmp_afp, mm_wp |
---|
| 68 | IMPLICIT NONE |
---|
| 69 | REAL(kind=mm_wp), INTENT(in) :: k !! k Order of the moment. |
---|
| 70 | REAL(kind=mm_wp) :: res !! Alpha value. |
---|
| 71 | res = SUM(dexp(mmp_afp%a*k**2+mmp_afp%b*k+mmp_afp%c)) |
---|
| 72 | RETURN |
---|
| 73 | END FUNCTION mm_alpha_f |
---|
| 74 | |
---|
| 75 | FUNCTION mm_ps2s(rcs,k,flow,t,p) RESULT(res) |
---|
| 76 | !! Get the proportion of aerosols that remains in the spherical mode during SS coagulation. |
---|
| 77 | !! |
---|
| 78 | !! From __k__ and __flow__ values, the method selects one of the four probability datasets datasets |
---|
| 79 | !! in [[mmp_globals(module)]] module (for instance [[mmp_globals(module):mmp_pco0p(variable)]]) |
---|
| 80 | !! and interpolates linearly probability for the given value of __rcs__, __t__ and __p__. |
---|
| 81 | !! |
---|
| 82 | !! @warning |
---|
| 83 | !! Here, the method assumes the datasets define the probability for __spherical__ particles to |
---|
| 84 | !! be transferred in the __fractal__ mode, but returns the proportion of particles that remains |
---|
| 85 | !! in the mode (which is expected by mp2m model). |
---|
| 86 | !! |
---|
| 87 | !! @attention |
---|
| 88 | !! If value cannot be interpolated, the method aborts the program. Normally, it cannot happen |
---|
| 89 | !! since we extrapolate the probability for characteristic radius value out of range. |
---|
| 90 | !! |
---|
| 91 | !! @attention |
---|
| 92 | !! Consequently, as the probability can only range from 0 to 1, it is wise to ensure that the |
---|
| 93 | !! look-up table limits this range: To do so, one can just add two values at the start and end |
---|
| 94 | !! of the table with probabilities respectively set to 0 and 1. |
---|
| 95 | USE LINTDSET |
---|
| 96 | USE LOCATORS |
---|
| 97 | USE MMP_GCM, ONLY : mmp_pco0p,mmp_pfm0p,mmp_pco3p,mmp_pfm3p,mmp_w_ps2s,mm_wp |
---|
| 98 | IMPLICIT NONE |
---|
| 99 | REAL(kind=mm_wp), INTENT(in) :: rcs |
---|
| 100 | !! Characteristic radius of the spherical size-distribution (m). |
---|
| 101 | INTEGER, INTENT(in) :: k |
---|
| 102 | !! Order of the moment (0 or 3). |
---|
| 103 | INTEGER, INTENT(in) :: flow |
---|
| 104 | !! Flow regime indicator (0: Continous, 1: Free-molecular). |
---|
| 105 | REAL(kind=mm_wp), INTENT(in) :: t |
---|
| 106 | !! Temperature (K). |
---|
| 107 | REAL(kind=mm_wp), INTENT(in) :: p |
---|
| 108 | !! Pressure level (Pa). |
---|
| 109 | REAL(kind=mm_wp) :: res |
---|
| 110 | !! Proportion of spherical particles that stay in the spherical mode during SS coagulation. |
---|
| 111 | TYPE(dset1d), POINTER :: pp |
---|
| 112 | res = 1._mm_wp |
---|
| 113 | IF (rcs <= 0.0_mm_wp .OR. .NOT.mmp_w_ps2s) RETURN |
---|
| 114 | SELECT CASE(k+flow) |
---|
| 115 | CASE(0) ; pp => mmp_pco0p ! 0 = 0 + 0 -> M0 / CO |
---|
| 116 | CASE(1) ; pp => mmp_pfm0p ! 1 = 0 + 1 -> M0 / FM |
---|
| 117 | CASE(3) ; pp => mmp_pco3p ! 3 = 3 + 0 -> M3 / CO |
---|
| 118 | CASE(4) ; pp => mmp_pfm3p ! 4 = 3 + 1 -> M3 / FM |
---|
| 119 | CASE DEFAULT ; RETURN |
---|
| 120 | END SELECT |
---|
| 121 | IF (.NOT.hdcd_lint_dset(rcs,pp,locate_reg_ext,res)) THEN |
---|
| 122 | WRITE(*,'(a)') "mm_moments:ps2s_sc: Cannot interpolate transfert probability" |
---|
| 123 | call EXIT(10) |
---|
| 124 | ELSE |
---|
| 125 | ! 05102017: do not care anymore for bad extrapolation: |
---|
| 126 | ! Bound probability value between 0 and 1 |
---|
| 127 | ! note: The input look-up table still must have strict monotic variation or |
---|
| 128 | ! awkward results can be produced. |
---|
| 129 | res = MAX(0.0_mm_wp,MIN(res,1.0_mm_wp)) |
---|
| 130 | ! we have interpolated f = 1-p and we need p ! |
---|
| 131 | res = 1._mm_wp - res |
---|
| 132 | ENDIF |
---|
| 133 | END FUNCTION mm_ps2s |
---|
| 134 | |
---|
| 135 | FUNCTION mm_qmean(rc1,rc2,order,modes,temp,pres) RESULT(res) |
---|
| 136 | !! Get the electric correction for coagulation kernel. |
---|
| 137 | !! |
---|
| 138 | !! The method computes the eletric charging correction to apply to the coagulation |
---|
| 139 | !! kernel as a function of the temperature, pressure and the characteristic radius of |
---|
| 140 | !! the mode involved in the coagulation. |
---|
| 141 | !! |
---|
| 142 | !! Modes are referred by a two letters uppercase string with the combination of: |
---|
| 143 | !! |
---|
| 144 | !! - S : spherical mode |
---|
| 145 | !! - F : fractal mode |
---|
| 146 | !! |
---|
| 147 | !! For example, SS means intra-modal coagulation for spherical particles. |
---|
| 148 | !! |
---|
| 149 | !! Here the electric charging correction is computed using linear interpolation from |
---|
| 150 | !! pre-tabulated values. |
---|
| 151 | USE LINTDSET |
---|
| 152 | USE LOCATORS |
---|
| 153 | USE MMP_GCM, ONLY : mmp_w_qe,mmp_qbsf0,mmp_qbsf3,mmp_qbff0, & |
---|
| 154 | mmp_qbsf0_e,mmp_qbsf3_e,mmp_qbff0_e,mm_wp |
---|
| 155 | IMPLICIT NONE |
---|
| 156 | REAL(kind=mm_wp), INTENT(in) :: rc1 !! Characteristic radius of the first mode (m). |
---|
| 157 | REAL(kind=mm_wp), INTENT(in) :: rc2 !! Characteristic radius of the the second mode (m). |
---|
| 158 | INTEGER, INTENT(in) :: order !! Moment's order (0 or 3 expected). |
---|
| 159 | CHARACTER(len=2), INTENT(in) :: modes !! Interaction mode (a combination of [S,F]). |
---|
| 160 | REAL(kind=mm_wp), INTENT(in) :: temp !! Temperature (K). |
---|
| 161 | REAL(kind=mm_wp), INTENT(in) :: pres !! Pressure level (Pa). |
---|
| 162 | REAL(kind=mm_wp) :: res !! Electric charging correction. |
---|
| 163 | INTEGER :: chx,np |
---|
| 164 | REAL(kind=mm_wp) :: vmin,vmax |
---|
| 165 | REAL(kind=mm_wp) :: r_tmp, t_tmp |
---|
| 166 | chx = 0 |
---|
| 167 | IF (.NOT.mmp_w_qe) THEN |
---|
| 168 | res = 1._mm_wp |
---|
| 169 | RETURN |
---|
| 170 | ENDIF |
---|
| 171 | |
---|
| 172 | IF (SCAN(modes(1:1),"sS") /= 0) chx = chx + 1 |
---|
| 173 | IF (SCAN(modes(2:2),"sS") /= 0) chx = chx + 1 |
---|
| 174 | IF (SCAN(modes(1:1),"fF") /= 0) chx = chx + 3 |
---|
| 175 | IF (SCAN(modes(2:2),"fF") /= 0) chx = chx + 3 |
---|
| 176 | chx = chx + order |
---|
| 177 | SELECT CASE(chx) |
---|
| 178 | CASE(2) ! M0/SS |
---|
| 179 | res = 1._mm_wp |
---|
| 180 | CASE(4) ! M0/SF |
---|
| 181 | ! Fix max values of input parameters |
---|
| 182 | r_tmp = MAX(MIN(log(rc1),mmp_qbsf0_e(2,2)),mmp_qbsf0_e(2,1)) |
---|
| 183 | t_tmp = MAX(MIN(temp,mmp_qbsf0_e(1,2)),mmp_qbsf0_e(1,1)) |
---|
| 184 | ! Interpolates values |
---|
| 185 | IF (.NOT.hdcd_lint_dset(t_tmp,r_tmp,mmp_qbsf0,locate_reg,res)) THEN |
---|
| 186 | WRITE(*,'(a)') "mm_moments:mm_qmean: Cannot interpolate mean Qelec" |
---|
| 187 | call EXIT(10) |
---|
| 188 | ENDIF |
---|
| 189 | CASE(5) ! M3/SS |
---|
| 190 | res = 1._mm_wp |
---|
| 191 | CASE(6) ! M0/FF |
---|
| 192 | r_tmp = MAX(MIN(log(rc1),mmp_qbff0_e(2,2)),mmp_qbff0_e(2,1)) |
---|
| 193 | t_tmp = MAX(MIN(temp,mmp_qbff0_e(1,2)),mmp_qbff0_e(1,1)) |
---|
| 194 | IF (.NOT.hdcd_lint_dset(t_tmp,r_tmp,mmp_qbff0,locate_reg,res)) THEN |
---|
| 195 | WRITE(*,'(a)') "mm_moments:mm_qmean: Cannot interpolate mean Qelec" |
---|
| 196 | call EXIT(10) |
---|
| 197 | ENDIF |
---|
| 198 | CASE(7) ! M3/SF |
---|
| 199 | r_tmp = MAX(MIN(log(rc1),mmp_qbsf3_e(2,2)),mmp_qbsf3_e(2,1)) |
---|
| 200 | t_tmp = MAX(MIN(temp,mmp_qbsf3_e(1,2)),mmp_qbsf3_e(1,1)) |
---|
| 201 | IF (.NOT.hdcd_lint_dset(t_tmp,r_tmp,mmp_qbsf3,locate_reg,res)) THEN |
---|
| 202 | WRITE(*,'(a)') "mm_moments:mm_qmean: Cannot interpolate mean Qelec" |
---|
| 203 | call EXIT(10) |
---|
| 204 | ENDIF |
---|
| 205 | CASE DEFAULT ! anything else :) |
---|
| 206 | res = 1._mm_wp |
---|
| 207 | END SELECT |
---|
| 208 | RETURN |
---|
| 209 | END FUNCTION mm_qmean |
---|
| 210 | |
---|
| 211 | PURE FUNCTION mm_get_btk(t,k) RESULT(res) |
---|
| 212 | !! Get the \(b_{k}^{T}\) coefficient of the Free Molecular regime. |
---|
| 213 | !! |
---|
| 214 | !! The method get the value of the Free-molecular regime coagulation pre-factor \(b_{k}^{T}\). |
---|
| 215 | !! For more details about this coefficient, please read [Coagulation](page/haze.html#coagulation) |
---|
| 216 | !! documentation page. |
---|
| 217 | !! |
---|
| 218 | !! @warning |
---|
| 219 | !! __k__ can only be one of the following value : 0 or 3. __t__ ranges only from 1 to 5. |
---|
| 220 | USE MMP_GCM, ONLY : mmp_bt0,mmp_bt3,mm_wp |
---|
| 221 | IMPLICIT NONE |
---|
| 222 | INTEGER, INTENT(in) :: t !! Type index of the \(b_{k}^{T}\) coefficient to get |
---|
| 223 | INTEGER, INTENT(in) :: k !! Moment Order of the \(b_{k}^{T}\) coefficient to get |
---|
| 224 | REAL(kind=mm_wp) :: res !! \(b_{k}^{T}\) coefficient |
---|
| 225 | IF (.NOT.(k == 3 .OR. k == 0)) res = 0._mm_wp |
---|
| 226 | IF (t > 5 .OR. t < 1) res = 0._mm_wp |
---|
| 227 | IF (k == 0) THEN |
---|
| 228 | res = mmp_bt0(t) |
---|
| 229 | ELSE IF (k == 3) THEN |
---|
| 230 | res = mmp_bt3(t) |
---|
| 231 | ENDIF |
---|
| 232 | RETURN |
---|
| 233 | END FUNCTION mm_get_btk |
---|
| 234 | |
---|
| 235 | ELEMENTAL FUNCTION mm_eta_g(t) RESULT (res) |
---|
| 236 | !! Get the air viscosity at a given temperature. |
---|
| 237 | !! |
---|
| 238 | !! The function computes the air viscosity at temperature __t__ using Sutherland method. |
---|
| 239 | USE MMP_GCM, ONLY: mm_wp |
---|
| 240 | IMPLICIT NONE |
---|
| 241 | REAL(kind=mm_wp), INTENT(in) :: t !! Temperature (K). |
---|
| 242 | REAL(kind=mm_wp) :: res !! Air viscosity at given temperature (\(Pa.s^{-1}\)). |
---|
| 243 | REAL (kind=mm_wp), PARAMETER :: eta0 = 1.75e-5_mm_wp, & |
---|
| 244 | tsut = 109._mm_wp, & |
---|
| 245 | tref = 293._mm_wp |
---|
| 246 | res = eta0 *dsqrt(t/tref)*(1._mm_wp+tsut/tref)/(1._mm_wp+tsut/t) |
---|
| 247 | RETURN |
---|
| 248 | END FUNCTION mm_eta_g |
---|
| 249 | |
---|
| 250 | ELEMENTAL FUNCTION mm_lambda_g(t,p) RESULT(res) |
---|
| 251 | !! Get the air mean free path at given temperature and pressure. |
---|
| 252 | !! |
---|
| 253 | !! The method computes the air mean free path: |
---|
| 254 | !! |
---|
| 255 | !! $$ \lambda_{g} = \dfrac{k_{b}T}{4\sqrt{2}\pi r_{a}^2 P} $$ |
---|
| 256 | !! |
---|
| 257 | !! Where \(\lambda_{g}\), is the air mean free path, \(k_{b}\) the Boltzmann constant, T the |
---|
| 258 | !! temperature, P the pressure level and \(r_{a}\) the radius of an _air molecule_. |
---|
| 259 | USE MMP_GCM, ONLY: mm_wp,mm_pi,mm_air_rad,mm_kboltz |
---|
| 260 | IMPLICIT NONE |
---|
| 261 | REAL(kind=mm_wp), INTENT(in) :: t !! Temperature (K). |
---|
| 262 | REAL(kind=mm_wp), INTENT(in) :: p !! Pressure level (Pa). |
---|
| 263 | REAL(kind=mm_wp) :: res !! Air mean free path (m). |
---|
| 264 | res = mm_kboltz*t/(4._mm_wp*dsqrt(2._mm_wp)*mm_pi*(mm_air_rad**2)*p) |
---|
| 265 | RETURN |
---|
| 266 | END FUNCTION mm_lambda_g |
---|