Newer
Older
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
MODULE MODI_AERO_EFFIC3D
!! ########################
!!
!
INTERFACE
!!
SUBROUTINE AERO_EFFIC3D(PRG,PVGG, & !aerosol radius/fall speed (m/s)
PRHODREF, & !Air density
PMUW, PMU, & !mu water/air
PDPG, & !diffusivity
PURR, & ! Rain water m.r. at time t
KMODE, & ! Number of aerosol modes
PTEMP, PCOR, & ! air temp, cunningham corr factor
PDENSITY_AER, & ! aerosol density
PEFFIC_AER ) ! scavenging efficiency for aerosol
!
IMPLICIT NONE
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PRG, PVGG
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODREF
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PDPG
REAL, DIMENSION(:,:,:), INTENT(IN) :: PMU, PMUW
REAL, DIMENSION(:,:,:), INTENT(IN) :: PURR
REAL, DIMENSION(:,:,:), INTENT(IN) :: PTEMP
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PCOR
INTEGER, INTENT(IN) :: KMODE
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PDENSITY_AER
REAL, DIMENSION(:,:,:,:), INTENT(INOUT):: PEFFIC_AER
END SUBROUTINE AERO_EFFIC3D
!!
END INTERFACE
END MODULE MODI_AERO_EFFIC3D
! ######spll
SUBROUTINE AERO_EFFIC3D(PRG,PVGG, & !aerosol radius/fall speed (m/s)
PRHODREF, & !Air density
PMUW, PMU, & !mu water/air
PDPG, & !diffusivity
PURR, & ! Rain water m.r. at time t
KMODE, & ! Number of aerosol modes
PTEMP, PCOR, & ! air temp, cunningham corr factor
PDENSITY_AER, & ! aerosol density
PEFFIC_AER ) ! scavenging efficiency for aerosol
!! #######################################
!!**********AERO_EFFIC3D**********
!! PURPOSE
!! -------
!! Calculate the collection efficiency of
! a falling drop interacting with a dust aerosol
! for use with aer_wet_dep_kmt_warm.f90
!!
!!** METHOD
!! ------
!! Using basic theory, and the one dimensional variables sent
!! from aer_wet_dep_kmt_warm.f90, calculation of the average
!! fall speed calculations, chapter 17.3.4, MESONH Handbook
!! droplet number based on the Marshall_Palmer distribution
!! and Stokes number, Reynolds number, etc. based on theory
!! (S&P, p.1019)
!!
!! REFERENCE
!! ---------
!! Seinfeld and Pandis p.1019
!! MESONH Handbook chapter 17.3.4
!!
!! AUTHOR
!! ------
!! K. Crahan Kaku / P. Tulet (CNRM/GMEI)
!!
!! MODIFICATIONS
!! -------------
!!
!-----------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------
!
USE MODD_RAIN_ICE_PARAM
USE MODD_RAIN_ICE_DESCR
USE MODD_CST, ONLY : XPI, XRHOLW, XP00, XRD
USE MODD_PARAMETERS , ONLY : JPVEXT
USE MODD_REF, ONLY : XTHVREFZ
!
IMPLICIT NONE
!
!* 0.1 declarations of arguments
!
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PRG, PVGG
REAL, DIMENSION(:,:,:), INTENT(IN) :: PRHODREF
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PDPG
REAL, DIMENSION(:,:,:), INTENT(IN) :: PMU, PMUW
REAL, DIMENSION(:,:,:), INTENT(IN) :: PURR
REAL, DIMENSION(:,:,:), INTENT(IN) :: PTEMP
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PCOR
INTEGER, INTENT(IN) :: KMODE
REAL, DIMENSION(:,:,:,:), INTENT(IN) :: PDENSITY_AER
REAL, DIMENSION(:,:,:,:), INTENT(INOUT):: PEFFIC_AER
!
!* 0.2 declaration of local variables
!
INTEGER :: IKB ! Coordinates of the first physical
! points along z
REAL :: ZRHO00 ! Surface reference air density
!viscosity ratio, Reynolds number
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3)) :: ZOMG, ZREY
!rain radius, m, and rain fall speed, m/s; aerosol radius (m),
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3)) :: ZRR, ZVR
!lambda, number concentration according to marshall palmer,
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3)) :: ZNT, ZLBDA
! Rain water m.r. source
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3)) :: ZRRS
!RHO_dref*r_r, Rain LWC
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3)) :: ZRLWC
! schmidts number
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3),KMODE) :: ZSCH
!
!Stokes number, ratio of diameters,aerosol radius
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3),KMODE) :: ZSTO, ZPHI, ZRG
! S Star Term
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3)) :: ZSTA, ZDIFF, ZTAU
!
!Term 1, Term 2, Term 3, Term 4 such that
! E = Term1 * Term 2 + Term 3 + Term 4
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3),KMODE) :: ZT1, ZT2
REAL, DIMENSION(SIZE(PRG,1),SIZE(PRG,2),SIZE(PRG,3),KMODE) :: ZT3, ZT4
!
INTEGER :: JI,JK
!
!-----------------------------------------------------------------
ZLBDA = 1E20
ZNT = 1E-20
ZRR = 10E-6
ZRRS(:,:,:)=PURR(:,:,:)
IKB = 1 + JPVEXT
ZRHO00 = XP00/(XRD*XTHVREFZ(IKB))
ZRG(:,:,:,:)=PRG(:,:,:,:)*1.E-6 !change units to meters
!
!Fall Speed calculations
!similar to rain_ice.f90, chapter 17.3.4, MESONH Handbook
!
ZVR (:,:,:)= XFSEDR * ZRRS(:,:,:)**(XEXSEDR-1) * &
PRHODREF(:,:,:)**(XEXSEDR-XCEXVT-1)
! Drop Radius calculation in m
!lbda = pi*No*rho(lwc)/(rho(dref)*rain rate) p.212 MESONH Handbook
! compute the slope parameter Lbda_r
WHERE((ZRRS(:,:,:).GT. 0.).AND.(PRHODREF(:,:,:) .GT. 0.))
ZLBDA(:,:,:) = XLBR*(PRHODREF(:,:,:)*ZRRS(:,:,:))**XLBEXR
!Number concentration NT=No/lbda p. 415 Jacobson
ZNT(:,:,:) = XCCR/ZLBDA(:,:,:)
!rain lwc (kg/m3) = rain m.r.(kg/kg) * rho_air(kg/m3)
ZRLWC(:,:,:)=ZRRS(:,:,:)*PRHODREF(:,:,:)
!4/3 *pi *r*NT*rho_eau(kg/m3) =rho(lwc)=rho(air)* qc(kg/kg)
ZRR(:,:,:) = (ZRLWC(:,:,:)/(XRHOLW*ZNT(:,:,:)*4./3.*XPI))**(1./3.)
END WHERE
ZRR(:,:,:) = MIN(ZRR(:,:,:), 100.E-6)
!Fall speed cannot be faster than 7 m/s
ZVR (:,:,:)=MIN(ZVR (:,:,:),7.)
!Ref SEINFELD AND PANDIS p.1019
! Viscosity Ratio
ZOMG(:,:,:)=PMUW(:,:,:)/PMU(:,:,:)
!!Reynolds number
ZREY(:,:,:)=ZRR(:,:,:)*ZVR(:,:,:)*PRHODREF(:,:,:)/PMU(:,:,:)
ZREY(:,:,:)= MAX(ZREY(:,:,:), 1E-2)
!S Star
ZSTA(:,:,:)=(1.2+(1/12)*LOG(1+ZREY(:,:,:)))/(1+LOG(1+ZREY(:,:,:)))
PEFFIC_AER(:,:,:,:)=0.0
DO JI=1,KMODE
!
!Scmidts number
ZSCH(:,:,:,JI)=PMU(:,:,:)/PRHODREF(:,:,:)/PDPG(:,:,:,JI)
! Rain-Aerosol relative velocity
ZDIFF(:,:,:) = MAX(ZVR(:,:,:)-PVGG(:,:,:,JI),0.)
! Relaxation time
ZTAU(:,:,:) = (ZRG(:,:,:,JI)*2.)**2. * PDENSITY_AER(:,:,:,JI) * PCOR(:,:,:,JI) / (18.*PMU(:,:,:))
! Stockes number
ZSTO(:,:,:,JI)= ZTAU(:,:,:) * ZDIFF(:,:,:) / ZRR(:,:,:)
!Ratio of diameters
ZPHI(:,:,:,JI)=ZRG(:,:,:,JI)/ZRR(:,:,:)
ZPHI(:,:,:,JI)=MIN(ZPHI(:,:,:,JI), 1.)
!Term 1
ZT1(:,:,:,JI)=4.0/ZREY(:,:,:)/ZSCH(:,:,:,JI)
!Term 2
ZT2(:,:,:,JI)=1.0+(0.4*ZREY(:,:,:)**(0.5)*ZSCH(:,:,:,JI)**(1./3.))+ &
(0.16*ZREY(:,:,:)**(0.5)*ZSCH(:,:,:,JI)**(0.5))
!Brownian diffusion
ZT1(:,:,:,JI)= ZT1(:,:,:,JI)*ZT2(:,:,:,JI)
!Term 3 - interception
ZT3(:,:,:,JI)=4.*ZPHI(:,:,:,JI)*(1./ZOMG(:,:,:)+ &
(1.0+(2.0*ZREY(:,:,:)**0.5))*ZPHI(:,:,:,JI))
ZT4(:,:,:,JI)=0.0
WHERE(ZSTO(:,:,:,JI).GT.ZSTA(:,:,:))
!Term 4 - impaction
ZT4(:,:,:,JI)=((ZSTO(:,:,:,JI)-ZSTA(:,:,:))/ &
(ZSTO(:,:,:,JI)-ZSTA(:,:,:)+2./3.))**(3./2.) &
*((XRHOLW/PDENSITY_AER(:,:,:,JI))**(1./2.))
END WHERE
!Collision Efficiancy
PEFFIC_AER(:,:,:,JI)=ZT1(:,:,:,JI)+ ZT3(:,:,:,JI)+ZT4(:,:,:,JI)
! Physical radius of a rain collector droplet up than 20 um
WHERE (ZRR(:,:,:) .LE. 9.9E-6)
PEFFIC_AER(:,:,:,JI)= 0.
END WHERE
ENDDO
PEFFIC_AER(:,:,:,:)=MIN(PEFFIC_AER(:,:,:,:),1.0)
PEFFIC_AER(:,:,:,:)=MAX(PEFFIC_AER(:,:,:,:),0.0)
END SUBROUTINE AERO_EFFIC3D