Changeset 3083 for trunk/LMDZ.TITAN/libf/muphytitan/mmp_moments.f90
- Timestamp:
- Oct 12, 2023, 10:30:22 AM (15 months ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.TITAN/libf/muphytitan/mmp_moments.f90
r1897 r3083 1 ! Copyright 2013-2015,2017 Université de Reims Champagne-Ardenne1 ! Copyright 2013-2015,2017,2022 Université de Reims Champagne-Ardenne 2 2 ! Contributor: J. Burgalat (GSMA, URCA) 3 3 ! email of the author : jeremie.burgalat@univ-reims.fr 4 ! 4 ! 5 5 ! This software is a computer program whose purpose is to compute 6 6 ! microphysics processes using a two-moments scheme. 7 ! 7 ! 8 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, 9 ! abiding by the rules of distribution of free software. You can use, 10 10 ! modify and/ or redistribute the software under the terms of the CeCILL 11 11 ! license as circulated by CEA, CNRS and INRIA at the following URL 12 ! "http://www.cecill.info". 13 ! 12 ! "http://www.cecill.info". 13 ! 14 14 ! As a counterpart to the access to the source code and rights to copy, 15 15 ! modify and redistribute granted by the license, users are provided only 16 16 ! with a limited warranty and the software's author, the holder of the 17 17 ! economic rights, and the successive licensors have only limited 18 ! liability. 19 ! 18 ! liability. 19 ! 20 20 ! In this respect, the user's attention is drawn to the risks associated 21 21 ! with loading, using, modifying and/or developing or reproducing the … … 25 25 ! professionals having in-depth computer knowledge. Users are therefore 26 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 ! 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 31 ! The fact that you are presently reading this means that you have had 32 32 ! knowledge of the CeCILL license and that you accept its terms. … … 35 35 !! summary: YAMMS/MP2M model external methods 36 36 !! author: J. Burgalat 37 !! date: 2013-2015,2017 37 !! date: 2013-2015,2017,2022 38 38 !! 39 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 40 !! for mp2m library. 41 !! 42 !! All the methods defined here satisify the interfaces defined in __m_interfaces__ module 43 43 !! of YAMMS library. 44 44 45 45 PURE FUNCTION mm_alpha_s(k) RESULT (res) 46 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 47 !! 48 !! The method computes the relation between the kth order moment and the 0th 49 49 !! order moment of the size-distribution law: 50 50 !! … … 58 58 res = SUM(dexp(mmp_asp%a*k**2+mmp_asp%b*k+mmp_asp%c)) 59 59 RETURN 60 END FUNCTION mm_alpha_s 60 END FUNCTION mm_alpha_s 61 61 62 62 PURE FUNCTION mm_alpha_f(k) RESULT (res) … … 81 81 !! 82 82 !! @warning 83 !! Here, the method assumes the datasets define the probability for __spherical__ particles to 83 !! Here, the method assumes the datasets define the probability for __spherical__ particles to 84 84 !! be transferred in the __fractal__ mode, but returns the proportion of particles that remains 85 85 !! in the mode (which is expected by mp2m model). 86 86 !! 87 87 !! @attention 88 !! If value cannot be interpolated, the method aborts the program. Normally, it cannot happen 88 !! If value cannot be interpolated, the method aborts the program. Normally, it cannot happen 89 89 !! since we extrapolate the probability for characteristic radius value out of range. 90 90 !! 91 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 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 94 !! of the table with probabilities respectively set to 0 and 1. 95 95 USE LINTDSET … … 111 111 TYPE(dset1d), POINTER :: pp 112 112 res = 1._mm_wp 113 IF (rcs <= 0.0_mm_wp .OR. .NOT.mmp_w_ps2s) RETURN 113 IF (rcs <= 0.0_mm_wp .OR. .NOT.mmp_w_ps2s) RETURN 114 114 SELECT CASE(k+flow) 115 115 CASE(0) ; pp => mmp_pco0p ! 0 = 0 + 0 -> M0 / CO … … 119 119 CASE DEFAULT ; RETURN 120 120 END SELECT 121 IF (.NOT.hdcd_lint_dset(rcs,pp,locate_reg_ext,res)) THEN 121 IF (.NOT.hdcd_lint_dset(rcs,pp,locate_reg_ext,res)) THEN 122 122 WRITE(*,'(a)') "mm_moments:ps2s_sc: Cannot interpolate transfert probability" 123 123 call EXIT(10) 124 124 ELSE 125 ! 05102017: do not care anymore for bad extrapolation: 125 ! 05102017: do not care anymore for bad extrapolation: 126 126 ! Bound probability value between 0 and 1 127 127 ! note: The input look-up table still must have strict monotic variation or … … 139 139 !! kernel as a function of the temperature, pressure and the characteristic radius of 140 140 !! the mode involved in the coagulation. 141 !! 141 !! 142 142 !! Modes are referred by a two letters uppercase string with the combination of: 143 143 !! 144 144 !! - S : spherical mode 145 145 !! - F : fractal mode 146 !! 146 !! 147 147 !! For example, SS means intra-modal coagulation for spherical particles. 148 148 !! … … 159 159 CHARACTER(len=2), INTENT(in) :: modes !! Interaction mode (a combination of [S,F]). 160 160 REAL(kind=mm_wp), INTENT(in) :: temp !! Temperature (K). 161 REAL(kind=mm_wp), INTENT(in) :: pres !! Pressure level (Pa). 161 REAL(kind=mm_wp), INTENT(in) :: pres !! Pressure level (Pa). 162 162 REAL(kind=mm_wp) :: res !! Electric charging correction. 163 163 INTEGER :: chx,np 164 164 REAL(kind=mm_wp) :: vmin,vmax 165 165 REAL(kind=mm_wp) :: r_tmp, t_tmp 166 chx = 0 166 chx = 0 167 167 IF (.NOT.mmp_w_qe) THEN 168 168 res = 1._mm_wp … … 177 177 SELECT CASE(chx) 178 178 CASE(2) ! M0/SS 179 res = 1._mm_wp 179 res = 1._mm_wp 180 180 CASE(4) ! M0/SF 181 181 ! Fix max values of input parameters … … 211 211 PURE FUNCTION mm_get_btk(t,k) RESULT(res) 212 212 !! Get the \(b_{k}^{T}\) coefficient of the Free Molecular regime. 213 !! 213 !! 214 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) 215 !! For more details about this coefficient, please read [Coagulation](page/haze.html#coagulation) 216 216 !! documentation page. 217 217 !! … … 244 244 tsut = 109._mm_wp, & 245 245 tref = 293._mm_wp 246 res = eta0 * dsqrt(t/tref)*(1._mm_wp+tsut/tref)/(1._mm_wp+tsut/t)246 res = eta0 * dsqrt(t/tref) * (1._mm_wp + tsut/tref) / (1._mm_wp + tsut/t) 247 247 RETURN 248 248 END FUNCTION mm_eta_g
Note: See TracChangeset
for help on using the changeset viewer.