GCC Code Coverage Report


Directory: ./
File: rad/su_aerp.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 79 79 100.0%
Branches: 66 68 97.1%

Line Branch Exec Source
1 1 SUBROUTINE SU_AERP
2
3 !**** *SU_AERP* - INITIALIZE MODULES YOEAERSRC, YOEAERSNK
4
5 ! PURPOSE.
6 ! --------
7 ! INITIALIZE YOEAERSRC AND YOEAERSNK, THE MODULES THAT CONTAINS
8 ! COEFFICIENTS NEEDED TO RUN THE PROGNOSTIC AEROSOLS
9
10 !** INTERFACE.
11 ! ----------
12 ! *CALL* *SU_AERP
13
14 ! EXPLICIT ARGUMENTS :
15 ! --------------------
16 ! NONE
17
18 ! IMPLICIT ARGUMENTS :
19 ! --------------------
20 ! YOEAERSRC, YOEAERSNK, YOEAERATM
21
22 ! METHOD.
23 ! -------
24 ! SEE DOCUMENTATION
25
26 ! EXTERNALS.
27 ! ----------
28
29 ! REFERENCE.
30 ! ----------
31 ! ECMWF RESEARCH DEPARTMENT DOCUMENTATION OF THE IFS
32
33 ! AUTHOR.
34 ! -------
35 ! JEAN-JACQUES MORCRETTE *ECMWF*
36 ! from O.BOUCHER (LOA, 1998-03)
37
38 ! MODIFICATIONS.
39 ! --------------
40 ! ORIGINAL : 2004-05-10
41
42 ! ------------------------------------------------------------------
43
44 USE PARKIND1 ,ONLY : JPRB
45 USE YOMHOOK ,ONLY : LHOOK, DR_HOOK
46
47 USE YOEAERSRC , ONLY : RSSFLX
48
49 USE YOEAERSNK , ONLY : R_R, R_S, RALPHAR, RALPHAS, RFRAER, RFRGAS, &
50 & RRHMAX, RRHTAB, RRHO_SS, RSSGROW, RMMD_SS, RMMD_DD, RRHO_DD, &
51 & RFRBC , RFRIF , RFROM , RFRSO4 , RFRDD , RFRSS , RHO_WAT, RHO_ICE, &
52 & RVDPOCE, RVDPSIC, RVDPLND, RVDPLIC, RVSEDOCE, RVSEDSIC, RVSEDLND, RVSEDLIC, &
53 & NBRH
54
55 USE YOEAERATM , ONLY : RMASSE, RMFMIN, NDD1, NSS1
56
57 IMPLICIT NONE
58
59 REAL(KIND=JPRB) :: ZHOOK_HANDLE
60 ! ----------------------------------------------------------------
61
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (LHOOK) CALL DR_HOOK('SU_AERP',0,ZHOOK_HANDLE)
62
63 !-- For the ECMWF model, the following tables when dimensioned to 12
64 ! can refer to 12 values of RH
65 ! (RHTAB, RHHO_SS, RSSGROW)
66 ! or to 12 types/bins of aerosols with the following mapping: NTYPAER
67 ! 1- 3 sea-salt 0.03 - 0.5 - 5 - 20 microns 1
68 ! 4- 6 dust 0.03 - 0.5 - 0.9 - 20 microns 2
69 ! 7- 8 POM hydrophilic, hydrophobic 3
70 ! 9-10 BC hydrophilic, hydrophobic 4
71 ! 11 sulfate 5
72 ! 12 fly ash 6
73 ! 13 stratospheric aerosols 7
74 ! 14 volcanic aerosols 8
75 ! 15 9
76 ! (RVDPOCE, RVDSIC, RVDPLND, RVDPLIC)
77 ! (RVSEDOCE,RVSEDSIC,RVSEDLND,RVSEDLIC)
78
79
80
81 !* 1. PARAMETERS RELATED TO SOURCES
82 ! -----------------------------
83
84 !-- OB's original 12 types and 24 different values had the following mapping
85 ! DMS SO2 SO4 H2S DMSO MSA H2O2
86 ! BC(2) OM(2) FlyAsh DU(2) SS(10)
87
88 !-- OB's original SS 10 bins
89 ! bin sizes: 0.03-0.06-0.13-0.25-0.5-1.0-2.0-5.0-10.-15.-20
90 !RSSFLX = (/ &
91 ! & 0.20526E-09_JPRB, 0.49292E-09_JPRB, 0.97079E-09_JPRB, 0.31938E-08_JPRB &
92 ! &, 0.16245E-07_JPRB, 0.86292E-07_JPRB, 0.31326E-06_JPRB, 0.24671E-06_JPRB &
93 ! &, 0.14109E-06_JPRB, 0.11784E-06_JPRB /)
94
95 ! maximum possible number of aerosol types
96 !NMAXTAER=9 already defined in SU_AERW
97
98 !N.B. Fluxes of sea salt for each size bin are given in mg m-2 s-1 at wind
99 ! speed of 1 m s-1 at 10m height (at 80% RH) in OB's seasalt.F
100 ! RSSFLX also in mg m-2 s-1
101 !-- OB's ECMWF 3 bins of sea salt: 0.03, 0.5, 5, 20 microns
102 1 RSSFLX = (/ 4.85963536E-09_JPRB, 4.15358556E-07_JPRB, 5.04905813E-07_JPRB /)
103
104 ! OB's original vdep_oce, vdep_sic, vdep_ter, vdep_lic were given over 24 values
105
106 ! following 12 values for 10 SS and 2 DU in cm s-1
107 !RVDPOCE = (/ 0.1_JPRB, 1.2_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB &
108 ! &, 0.1_JPRB, 1.2_JPRB, 1.2_JPRB, 1.2_JPRB, 1.5_JPRB, 1.5_JPRB /)
109 !
110 !RVDPSIC = (/ 0.1_JPRB, 1.2_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB &
111 ! &, 0.1_JPRB, 1.2_JPRB, 1.2_JPRB, 1.2_JPRB, 1.5_JPRB, 1.5_JPRB /)
112 !
113 !RVDPLND = (/ 0.1_JPRB, 1.2_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB &
114 ! &, 0.1_JPRB, 1.2_JPRB, 1.2_JPRB, 1.2_JPRB, 1.5_JPRB, 1.5_JPRB /)
115 !
116 !RVDPLIC = (/ 0.1_JPRB, 1.2_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB, 0.1_JPRB &
117 ! &, 0.1_JPRB, 1.2_JPRB, 1.2_JPRB, 1.2_JPRB, 1.5_JPRB, 1.5_JPRB /)
118
119
120
121 !* 2. PARAMETERS RELATED TO SINKS
122 ! ---------------------------
123
124 1 R_R = 0.001_JPRB
125 1 R_S = 0.001_JPRB
126
127 1 RFRAER = 0.5_JPRB
128 1 RFRGAS = 1.0_JPRB
129
130 !* 2.1 SEA SALT
131 ! --------
132 !-- parameters related to SEA SALT: 12 relates to 12 values of relative humidity
133
134 1 NBRH=12
135 1 RRHMAX = 95._JPRB
136 RRHTAB = (/ 0._JPRB, 10._JPRB, 20._JPRB, 30._JPRB, 40._JPRB, 50._JPRB &
137 1 & , 60._JPRB, 70._JPRB, 80._JPRB, 85._JPRB, 90._JPRB, 95._JPRB /)
138 RRHO_SS = (/ 2160._JPRB, 2160._JPRB, 2160._JPRB, 2160._JPRB, 1451.6_JPRB &
139 & , 1367.9_JPRB, 1302.9_JPRB, 1243.2_JPRB, 1182.7_JPRB, 1149.5_JPRB &
140 1 & , 1111.6_JPRB, 1063.1_JPRB /)
141 RSSGROW = (/ 0.503_JPRB, 0.503_JPRB, 0.503_JPRB, 0.503_JPRB, 0.724_JPRB &
142 & , 0.782_JPRB, 0.838_JPRB, 0.905_JPRB, 1.000_JPRB, 1.072_JPRB &
143 1 & , 1.188_JPRB, 1.447_JPRB /)
144
145 !-- OB's original 10 bins !RMMD_SS = (/ 0.09_JPRB, 0.19_JPRB, 0.38_JPRB, 0.75_JPRB, 1.50_JPRB &
146 ! & , 3.00_JPRB, 7.00_JPRB, 15.0_JPRB, 25.0_JPRB, 35.0_JPRB /)
147
148 !-- OB's ECMWF 3 bins of sea salt
149 ! bins are 0.03 - 0.5 - 5.0 - 20 microns
150
151 1 RMMD_SS = (/ 0.30_JPRB, 3.00_JPRB, 10.00_JPRB /)
152 1 RFRSS = (/ 0.7_JPRB, 0.7_JPRB, 0.7_JPRB /)
153 1 RHO_WAT = 1000._JPRB
154 1 RHO_ICE = 500._JPRB
155
156 !- computed off-line by gems_ss.f (m s-1)
157
158
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDOCE(1:3) = (/ 0.24E-04_JPRB, 0.20E-02_JPRB, 0.20E-01_JPRB /)
159
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDSIC(1:3) = (/ 0.24E-04_JPRB, 0.20E-02_JPRB, 0.20E-01_JPRB /)
160
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDLND(1:3) = (/ 0.24E-04_JPRB, 0.20E-02_JPRB, 0.20E-01_JPRB /)
161
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDLIC(1:3) = (/ 0.24E-04_JPRB, 0.20E-02_JPRB, 0.20E-01_JPRB /)
162
163 ! adapted from LMDZ (m s-1)
164
165
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVDPOCE(1:3) = (/ 0.100E-02_JPRB, 0.110E-01_JPRB, 0.145E-01_JPRB /)
166
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVDPSIC(1:3) = (/ 0.100E-02_JPRB, 0.110E-01_JPRB, 0.145E-01_JPRB /)
167
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVDPLND(1:3) = (/ 0.100E-02_JPRB, 0.110E-01_JPRB, 0.145E-01_JPRB /)
168
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 RVDPLIC(1:3) = (/ 0.100E-02_JPRB, 0.110E-01_JPRB, 0.145E-01_JPRB /)
169
170
171 !* 2.2 DESERT DUST
172 ! -----------
173 !- parameters related to DESERT DUST (OB's ECMWF 3 bins)
174 ! bins are 0.03 - 0.55 - 0.9 - 20 microns
175
176 1 RMMD_DD = (/ 0.32_JPRB, 0.75_JPRB, 9.0_JPRB /)
177 1 RRHO_DD = (/ 2600._JPRB, 2600._JPRB, 2600._JPRB /)
178 1 RFRDD = (/ 0.7_JPRB, 0.7_JPRB, 0.7_JPRB /)
179
180 !- computed off-line by gems_dust.f
181
182
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDOCE(4:6) = (/ 0.70E-04_JPRB, 0.20E-03_JPRB, 0.20E-02_JPRB /)
183
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDSIC(4:6) = (/ 0.70E-04_JPRB, 0.20E-03_JPRB, 0.20E-02_JPRB /)
184
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDLND(4:6) = (/ 0.70E-04_JPRB, 0.20E-03_JPRB, 0.20E-02_JPRB /)
185
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVSEDLIC(4:6) = (/ 0.70E-04_JPRB, 0.20E-03_JPRB, 0.20E-02_JPRB /)
186
187 ! adapted from LMDZ (m s-1)
188
189
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVDPOCE(4:6) = (/ 0.100E-02_JPRB, 0.500E-02_JPRB, 0.110E-01_JPRB /)
190
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVDPSIC(4:6) = (/ 0.100E-02_JPRB, 0.500E-02_JPRB, 0.110E-01_JPRB /)
191
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 RVDPLND(4:6) = (/ 0.100E-02_JPRB, 0.500E-02_JPRB, 0.110E-01_JPRB /)
192
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 RVDPLIC(4:6) = (/ 0.100E-02_JPRB, 0.500E-02_JPRB, 0.110E-01_JPRB /)
193
194
195 !* 2.3 OTHER AEROSOLS (to be improved later!)
196 ! --------------
197 !- parameters related to other aerosol types
198 !- particulate organic matter POM
199 1 RFROM = (/ 0.0_JPRB, 0.7_JPRB /)
200
201
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDOCE(7:8) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
202
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDSIC(7:8) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
203
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDLND(7:8) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
204
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDLIC(7:8) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
205
206 ! adapted from LMDZ (m s-1)
207
208
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVDPOCE(7:8) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
209
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVDPSIC(7:8) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
210
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVDPLND(7:8) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
211
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 RVDPLIC(7:8) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
212
213
214 !- black carbon
215 1 RFRBC = (/ 0.0_JPRB, 0.7_JPRB /)
216
217
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDOCE(9:10) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
218
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDSIC(9:10) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
219
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDLND(9:10) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
220
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVSEDLIC(9:10) = (/ 0.10E+00_JPRB, 0.10E+00_JPRB /)
221
222 ! adapted from LMDZ (m s-1)
223
224
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVDPOCE(9:10) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
225
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVDPSIC(9:10) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
226
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 RVDPLND(9:10) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
227
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 RVDPLIC(9:10) = (/ 0.10E-02_JPRB, 0.10E-02_JPRB /)
228
229 !- sulfate
230 1 RFRSO4 = 0.7_JPRB
231
232 1 RVSEDOCE(11) = 0.05_JPRB
233 1 RVSEDSIC(11) = 0.25_JPRB
234 1 RVSEDLND(11) = 0.25_JPRB
235 1 RVSEDLIC(11) = 0.25_JPRB
236
237 ! adapted from LMDZ (m s-1)
238
239 1 RVDPOCE(11) = 0.05E-02_JPRB
240 1 RVDPSIC(11) = 0.25E-02_JPRB
241 1 RVDPLND(11) = 0.25E-02_JPRB
242 1 RVDPLIC(11) = 0.25E-02_JPRB
243
244 !- fly ash
245 1 RFRIF = 0.7_JPRB
246
247 1 RVSEDOCE(12) = 0.20E+00_JPRB
248 1 RVSEDSIC(12) = 0.20E+00_JPRB
249 1 RVSEDLND(12) = 0.20E+00_JPRB
250 1 RVSEDLIC(12) = 0.20E+00_JPRB
251
252 ! adapted from LMDZ (m s-1)
253
254 1 RVDPOCE(12) = 0.20E-02_JPRB
255 1 RVDPSIC(12) = 0.20E-02_JPRB
256 1 RVDPLND(12) = 0.20E-02_JPRB
257 1 RVDPLIC(12) = 0.20E-02_JPRB
258
259
260
261
262 !- NB: 15 values for all possible types of ECMWF aerosols
263 RALPHAR = (/ &
264 & 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, &
265 1 & 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB, 0.001_JPRB /)
266 RALPHAS = (/ &
267 & 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, &
268 1 & 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB, 0.01_JPRB /)
269
270
271 !* 3. PARAMETERS RELATED TO TRANSPORT WITHIN THE FREE ATMOSPHERE
272 ! ----------------------------------------------------------
273
274 1 NDD1=4
275 1 NSS1=1
276
277 1 RMFMIN = 1.E-10_JPRB
278
279 RMASSE = (/ &
280 & 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB &
281 &, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB &
282 1 &, 6.02E+23_JPRB, 6.02E+23_JPRB, 6.02E+23_JPRB /)
283
284
285 ! ----------------------------------------------------------------
286
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (LHOOK) CALL DR_HOOK('SU_AERP',1,ZHOOK_HANDLE)
287 1 END SUBROUTINE SU_AERP
288
289