SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
mode_dslt_surf.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 !! ########################
7 !! ########################
8 !!
9 !
10 USE yomhook ,ONLY : lhook, dr_hook
11 USE parkind1 ,ONLY : jprb
12 !
13 IMPLICIT NONE
14 !
15  CONTAINS
16 !!
17 !! ############################################################
18 SUBROUTINE massflux2momentflux( &
19  pflux, & ! [kg/m2/s] for M3, zero for other]
20  prhodref, & ! [kg/m3] air density
21  pemisradius, & ! [um] emitted radius for the different modes
22  pemissig, & ! [-] emitted sigma for the different modes
23  kmde, &
24  pconvertfacm0, &
25  pconvertfacm6, &
26  pconvertfacm3, &
27  ovarsig, &
28  orgfix &
29  )
30 !! ############################################################
31 !!
32 !! PURPOSE
33 !! -------
34 !! Transform emissions in mass (kg/m2/sec) to emissions of moments which have
35 !! a bit strange units
36 !! MESONH carries the following units during transport:
37 !! M0=#/molec_{air}
38 !! M3=molec_{dst}/molec_{air}
39 !! M6=um6/molec_{air}*1.d6
40 !! The surface model should have (for dust)
41 !! M0=#/m3*[kg_{dst}/mole_{dst}/XAVOGADRO]
42 !! M3=kg/m3
43 !! M6=um6/m3
44 !!
45 !! REFERENCE
46 !! ---------
47 !! Tulet et al, ORILAM manuscript for transformation of modal parameters
48 !! J. Geophys. Res., 110, D18201, doi:10.1029/2004JD005716
49 !!
50 !! AUTHOR
51 !! ------
52 !! Alf Grini and Pierre TULET (CNRM/GMEI)
53 !!
54 !! MODIFICATIONS
55 !! -------------
56 !! J.Escobar 06/2013 for REAL4/8 add EPSILON management
57 !!
58 !!
59 !! EXTERNAL
60 !! --------
61 !! None
62 !!
63 IMPLICIT NONE
64 !!
65 !-------------------------------------------------------------------------------
66 !
67 !* 0. DECLARATIONS
68 ! ------------
69 !
70 !* 0.1 declarations of arguments
71 !
72 REAL, DIMENSION(:,:), INTENT(INOUT) :: pflux !In; kg/m2/s (index #2, #5, #8 etc)
73  !Out: mole particles per mole air m/s *(MWdst/MWair*rhoair)(index #1)
74  !Out: kg/m2/s (index #2)
75  !Out: moles m6/moles air m/s *(MWdst/MWair*rhoair)(index #3)
76 REAL, DIMENSION(:), INTENT(IN) :: prhodref !I [kg/m3] density of air
77 REAL, DIMENSION(:), INTENT(IN) :: pemisradius !I [um] emitted radius
78 REAL, DIMENSION(:), INTENT(IN) :: pemissig !I [-] emitted sigma for the modes
79 INTEGER, INTENT(IN) :: kmde
80 REAL, INTENT(IN) :: pconvertfacm0
81 REAL, INTENT(IN) :: pconvertfacm6
82 REAL, INTENT(IN) :: pconvertfacm3
83 LOGICAL, INTENT(IN) :: ovarsig
84 LOGICAL, INTENT(IN) :: orgfix
85 !
86 !* 0.2 declarations local variables
87 !
88 REAL,DIMENSION(SIZE(PFLUX,1),3) :: zfm !Intermediate variable to get moments
89 !
90 INTEGER :: jmode ! Counter for dust modes
91 INTEGER :: jsv_idx ! Counter for dust scalar variables
92 REAL(KIND=JPRB) :: zhook_handle
93 !
94 !-------------------------------------------------------------------------------
95 !
96 !MESONH carries the following units during transport:
97 !M0=#/molec_{air}
98 !M3=molec_{dst}/molec_{air}
99 !M6=um6/molec_{air}*1.d6
100 
101 !The surface should get the following units
102 !M0=#/m3*MW_DST/XAVOGADRO
103 !M3=kg/m3
104 !M6=um6/m3*1.d6 MW_DST/XAVOGADRO
105 
106 !Emissions of dust are in kg/m2/sec for mode 3 at this point
107 
108 !Factor which is needed so that all gains normal units when leaving ground paramn
109 IF (lhook) CALL dr_hook('MODE_DSLT_SURF:MASSFLUX2MOMENTFLUX',0,zhook_handle)
110 
111 !Initialize initermediate moments
112 zfm(:,:)=0.
113 
114 DO jmode=1,kmde
115 
116  !Make index which is 0 for first mode, 3 for second, 6 for third etc
117  IF (ovarsig) THEN
118  jsv_idx = (jmode-1)*3
119  ELSE IF (orgfix) THEN
120  jsv_idx = jmode-2
121  ELSE
122  jsv_idx = (jmode-1)*2
123  END IF
124 
125  !IN THIS VERSION, MASS FLUX (kg/m2/sec) IS SENT IN INDEX #2, #5, #8 if 3 moments per mode
126  !IF TWO MOMENTS PER MODE, MASS FLUX IS SENT AS INDEX #2, #4, #6
127 
128  !Get flux of number in #/m2/sec from flux of mass in kg/m2/sec
129  zfm(:,1) = pflux(:,jsv_idx+2) & ! kg_{dst}/m2/sec
130  / pemisradius(jmode)**3 & ! *um^{-3} ==> #/m2/sec*(m3/um3)
131  * exp(-4.5*(log(pemissig(jmode)))**2) & ! Take into account size distribution
132  / pconvertfacm3 ! /(kg_{dst}/m^{3}_{dst)} ==> m^3_{dst}/m2/sec
133 
134 
135  ! Get flux of moment 6 consistent with the other moments
136  zfm(:,3) = zfm(:,1) & ! [#/m3]
137  * (pemisradius(jmode)**6) & ! *um6 ==> um6/m2/sec
138  * exp(18. *(log(pemissig(jmode)))**2) ! Take into account size distribution
139 
140  !Get flux of Moment 0 in transport units
141  IF (.NOT.orgfix) THEN
142  pflux(:,jsv_idx+1) = zfm(:,1) & ! particles/m^2/sec
143  * pconvertfacm0 ! ==> particles/m2/sec * kg_dst/m3_{air}
144  END IF
145 
146  ! Flux moment 6
147  IF (ovarsig) THEN
148  pflux(:,jsv_idx+3) = zfm(:,3) & ! um^6/m^2/sec
149  * pconvertfacm6 ! ==>
150  ENDIF
151 
152  !Multiply with molecular weights so that you get back the units described above when
153  !when multiply with the opposite variable in ground_paramn.f90
154  !PFLUX(:,JSV_IDX+1) = PFLUX(:,JSV_IDX+1) * 100.E-3 * PRHODREF(:) / ZMD !#_{aer}/molec_{air} m/s * kg_{aer}/m^3_{air}
155  !IF (LVARSIG) PFLUX(:,JSV_IDX+3) = PFLUX(:,JSV_IDX+3) * 100.E-3 * PRHODREF(:) / ZMD !um^6_{aer}/molec_{air}*cm^3/m^3 m/s kg_{aer}/m^3_{air}
156  !
157  !
158 ENDDO !Loop on modes
159 !
160 IF (lhook) CALL dr_hook('MODE_DSLT_SURF:MASSFLUX2MOMENTFLUX',1,zhook_handle)
161 !
162 END SUBROUTINE massflux2momentflux
163 
164 !**********************************************************************
165 !**********************************************************************
166 !**********************************************************************
167 
168 SUBROUTINE dsltmoment2size( &
169  psvt, & !I [XX/m3] input scalar variables (moment of distribution)
170  prhodref, & !I [kg/m3] density of air
171  pemisradius, & ![um] emitted radius for the different modes
172  pemissig, & ![-] emitted sigma for the different modes
173  km0, &
174  km3, &
175  km6, &
176  pconvertfacm0, &
177  pconvertfacm6, &
178  pconvertfacm3, &
179  ovarsig, &
180  orgfix, &
181  psig1d, & !O [-] standard deviation of aerosol distribution
182  prg1d, & !O [um] number median diameter of aerosol distribution
183  pn1d, & !O [#/m3] number concentration of aerosols
184  pmass1d, & !O [kg/m3] mass concentration of aerosol
185  pm1d & !O aerosols moments 0, 3 and 6
186  )
187 !! ############################################################
188 !!
189 !! PURPOSE
190 !! -------
191 !! Translate the three moments M0, M3 and M6 given in ppp into
192 !! Values which can be understood more easily (R, sigma, N, M)
193 !! At this point, M3 is in kg/m3, M0 in #/m3*(kg_{dst}/mole), M6 in um6/m3*1.d6*(kg_{dst}/mole)
194 !!
195 !! All the moments have been transformed in MESONH (atmospheric model) so that the surface gets
196 !! M0 [#/m3] *XMOLARWEIGHT_DST/XAVOGADRO
197 !! M3 [kg/m3]
198 !! M6 [um6/m3*1.d6] *XMOLARWEIGHT_DST/XAVOGADRO
199 !!
200 !! REFERENCE
201 !! ---------
202 !! Tulet et al, ORILAM manuscript for transformation of modal parameters
203 !! J. Geophys. Res., 110, D18201, doi:10.1029/2004JD005716
204 !!
205 !! AUTHOR
206 !! ------
207 !! Pierre TULET (LA)
208 !!
209 !! MODIFICATIONS
210 !! -------------
211 !! Alf Grini (CNRM)
212 !!
213 !! EXTERNAL
214 !! --------
215 !!
216 USE modd_surf_par , ONLY : xsurf_tiny
217 !!
218 IMPLICIT NONE
219 !!
220 !-------------------------------------------------------------------------------
221 !
222 !* 0. DECLARATIONS
223 ! ------------
224 !
225 !* 0.1 declarations of arguments
226 !
227 !INPUT
228 REAL, DIMENSION(:,:), INTENT(IN) :: psvt !I [ppp] moments in surface units
229 REAL, DIMENSION(:), INTENT(IN) :: prhodref !I [kg/m3] density of air
230 REAL, DIMENSION(:), INTENT(IN) :: pemissig
231 REAL, DIMENSION(:), INTENT(IN) :: pemisradius
232 INTEGER,DIMENSION(:), INTENT(IN) :: km0 ! [idx] index for Mode 0 in passed variables
233 INTEGER,DIMENSION(:), INTENT(IN) :: km3 ! [idx] indexes for Mode 3 in passed variables
234 INTEGER,DIMENSION(:), INTENT(IN) :: km6 ! [idx] indexes for Mode 6 in passed variables
235 REAL, INTENT(IN) :: pconvertfacm0
236 REAL, INTENT(IN) :: pconvertfacm6
237 REAL, INTENT(IN) :: pconvertfacm3
238 LOGICAL, INTENT(IN) :: ovarsig
239 LOGICAL, INTENT(IN) :: orgfix
240 REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: psig1d !O [-] standard deviation
241 REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: prg1d !O [um] number median diameter
242 REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: pn1d !O [#/m3] number concentration
243 REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: pmass1d !O [kg_{aer}/m3] mass concentration
244 REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: pm1d !O aerosols moments (MESONH units)
245 !
246 !* 0.2 declarations local variables
247 !
248 REAL,DIMENSION(SIZE(PSVT,1), SIZE(PSVT,2)) :: zsv ! [dusts moment concentration]
249 REAL,DIMENSION(SIZE(PSVT,1), SIZE(KM0)*3) :: zm ! [moments] local array for moments
250 REAL,DIMENSION(SIZE(PSVT,1)) :: zsigma ! [-] standard deviation
251 REAL,DIMENSION(SIZE(PSVT,1)) :: zrg ! [um] number median diameter
252 INTEGER :: jn, j0, j3, j6 ! [idx] loop counters
253 REAL(KIND=JPRB) :: zhook_handle
254 !
255 ! 1.1 initialisation
256 !
257 !Get the conversion factors
258 IF (lhook) CALL dr_hook('MODE_DSLT_SURF:DSLTMOMENT2SIZE',0,zhook_handle)
259 !
260 !Get scalar variable indexes
261 !
262 !Save the moments in a local array
263 zsv(:,:) = max(psvt(:,:), xsurf_tiny)
264 !
265 DO jn=1,SIZE(km0)
266 
267  j0 = 1 + (jn-1)*3
268  j3 = 2 + (jn-1)*3
269  j6 = 3 + (jn-1)*3
270 
271  !calculate moment 3 from total aerosol mass in kg/m3 ==> um3/m3
272  zm(:,j3) = zsv(:,km3(jn)) & ! kg_{aer}/m3_{air}
273  / pconvertfacm3 ! ==> m3_{dst}/m3_{air}
274 
275  IF (ovarsig) THEN ! give M6 (case of variable standard deviation)
276 
277  !Get number concentration (#/molec_{air}==>#/m3)
278  zm(:,j0) = zsv(:,km0(jn)) & ! #/m3air*M_{dst}/avogadro
279  / pconvertfacm0 ! ==> #/m3
280 
281  !Calculate moment 6 from the sent value
282  zm(:,j6) = zsv(:,km6(jn)) & ! um6/m3_{air}*(cm3/m3)*M_{dst}/Avogadro
283  / pconvertfacm6 ! ==> um6/m3
284 
285  !Get sigma (only if sigma is allowed to vary)
286  !Get intermediate values for sigma M3^2/(M0*M6) (ORILAM paper, eqn 8)
287  zsigma(:) = zm(:,j3)**2 / (zm(:,j0)*zm(:,j6))
288  !Limit the intermediate value, can not be larger than 1
289  zsigma(:) = min(1-1e-10,zsigma(:))
290  !Limit the value for intermediate, can not be smaller than 0
291  zsigma(:) = max(1e-10,zsigma(:))
292  !Calculate log(sigma)
293  zsigma(:) = log(zsigma(:))
294  !Finally get the real sigma the negative sign is because of
295  !The way the equation is written (M3^2/(M0*M6)) instead of (M0*M6)/M3^3
296  zsigma(:) = exp(1./3.*sqrt(-zsigma(:)))
297 
298  ELSE IF (orgfix) THEN ! compute M6 from M3, Rg and SIGMA
299 
300  !Get the emitted sigma for this mode
301  zsigma(:) = pemissig(jn)
302 
303  zm(:,j0) = zm(:,j3) / &
304  ((pemisradius(km3(jn))**3)*exp(4.5 * log(zsigma(:))**2))
305 
306  ELSE ! compute M6 from M0, M3 and SIGMA
307 
308  !Get the emitted sigma for this mode
309  zsigma(:) = pemissig(jn)
310 
311  !Get number concentration (#/molec_{air}==>#/m3)
312  zm(:,j0) = zsv(:,km0(jn)) & ! #/m3air*M_{dst}/avogadro
313  / pconvertfacm0 ! ==> #/m3
314 
315  END IF
316 
317  !Calculate moment 6 from this emitted sigma
318  zm(:,j6) = zm(:,j0) * ((zm(:,j3)/zm(:,j0))**(1./3.) &
319  * exp(-(3./2.)*log(zsigma(:))**2))**6 &
320  * exp(18.*log(zsigma(:))**2)
321 
322  !Get number median radius (eqn. 7 in Orilam manuscript)
323  zrg(:) = ((zm(:,j3)**4) / (zm(:,j6)*zm(:,j0)**3)) ** (1./6.)
324 
325  !Give the sigma-values to the passed array
326  IF(present(psig1d)) psig1d(:,jn) = zsigma(:)
327 
328  !Set the number concentrations in the passed array
329  IF(present(pn1d)) pn1d(:,jn) = zm(:,j0)
330 
331  !Get the number median radius
332  IF(present(prg1d)) prg1d(:,jn)= zrg(:)
333 
334  IF(present(pmass1d))THEN
335  pmass1d(:,jn)= zm(:,j0) &!#/m^3_{air}
336  * pconvertfacm3 &
337  * zrg(:)**3 * exp(4.5*(log(zsigma(:)))**2)
338  ENDIF
339 
340 END DO !Loop on modes
341 
342 IF(present(pm1d)) pm1d(:,:) = zm(:,:)
343 
344 IF (lhook) CALL dr_hook('MODE_DST_SURF:DUSTMOMENT2SIZE',1,zhook_handle)
345 !
346 !
347 END SUBROUTINE dsltmoment2size
348 
349 
350 END MODULE mode_dslt_surf
subroutine massflux2momentflux(PFLUX, PRHODREF, PEMISRADIUS, PEMISSIG, KMDE, PCONVERTFACM0, PCONVERTFACM6, PCONVERTFACM3, OVARSIG, ORGFIX)
subroutine dsltmoment2size(PSVT, PRHODREF, PEMISRADIUS, PEMISSIG, KM0, KM3, KM6, PCONVERTFACM0, PCONVERTFACM6, PCONVERTFACM3, OVARSIG, ORGFIX, PSIG1D, PRG1D, PN1D, PMASS1D, PM1D)