1 | !********************************************************************** |
---|
2 | ! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010 * |
---|
3 | ! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa, * |
---|
4 | ! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann * |
---|
5 | ! * |
---|
6 | ! This file is part of FLEXPART. * |
---|
7 | ! * |
---|
8 | ! FLEXPART is free software: you can redistribute it and/or modify * |
---|
9 | ! it under the terms of the GNU General Public License as published by* |
---|
10 | ! the Free Software Foundation, either version 3 of the License, or * |
---|
11 | ! (at your option) any later version. * |
---|
12 | ! * |
---|
13 | ! FLEXPART is distributed in the hope that it will be useful, * |
---|
14 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of * |
---|
15 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * |
---|
16 | ! GNU General Public License for more details. * |
---|
17 | ! * |
---|
18 | ! You should have received a copy of the GNU General Public License * |
---|
19 | ! along with FLEXPART. If not, see <http://www.gnu.org/licenses/>. * |
---|
20 | !********************************************************************** |
---|
21 | |
---|
22 | subroutine readspecies(id_spec,pos_spec) |
---|
23 | |
---|
24 | !***************************************************************************** |
---|
25 | ! * |
---|
26 | ! This routine reads names and physical constants of chemical species/ * |
---|
27 | ! radionuclides given in the parameter pos_spec * |
---|
28 | ! * |
---|
29 | ! Author: A. Stohl * |
---|
30 | ! * |
---|
31 | ! 11 July 1996 * |
---|
32 | ! |
---|
33 | ! Changes: * |
---|
34 | ! N. Kristiansen, 31.01.2013: Including parameters for in-cloud scavenging * |
---|
35 | ! * |
---|
36 | ! HSO, 13 August 2013 |
---|
37 | ! added optional namelist input |
---|
38 | ! * |
---|
39 | !***************************************************************************** |
---|
40 | ! * |
---|
41 | ! Variables: * |
---|
42 | ! decaytime(maxtable) half time for radiological decay * |
---|
43 | ! specname(maxtable) names of chemical species, radionuclides * |
---|
44 | ! weta, wetb Parameters for determining below-cloud scavenging * |
---|
45 | ! weta_in Parameter for determining in-cloud scavenging * |
---|
46 | ! wetb_in Parameter for determining in-cloud scavenging * |
---|
47 | ! wetc_in Parameter for determining in-cloud scavenging * |
---|
48 | ! wetd_in Parameter for determining in-cloud scavenging * |
---|
49 | ! ohreact OH reaction rate * |
---|
50 | ! id_spec SPECIES number as referenced in RELEASE file * |
---|
51 | ! id_pos position where SPECIES data shall be stored * |
---|
52 | ! * |
---|
53 | ! Constants: * |
---|
54 | ! * |
---|
55 | !***************************************************************************** |
---|
56 | |
---|
57 | use par_mod |
---|
58 | use com_mod |
---|
59 | |
---|
60 | implicit none |
---|
61 | |
---|
62 | integer :: i, pos_spec,j |
---|
63 | integer :: idow,ihour,id_spec |
---|
64 | character(len=3) :: aspecnumb |
---|
65 | logical :: spec_found |
---|
66 | |
---|
67 | character(len=16) :: pspecies |
---|
68 | real :: pdecay, pweta, pwetb, preldiff, phenry, pf0, pdensity, pdquer |
---|
69 | real :: pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao |
---|
70 | real :: pweta_in, pwetb_in, pwetc_in, pwetd_in |
---|
71 | integer :: readerror |
---|
72 | |
---|
73 | ! declare namelist |
---|
74 | namelist /species_params/ & |
---|
75 | pspecies, pdecay, pweta, pwetb, & |
---|
76 | pweta_in, pwetb_in, pwetc_in, pwetd_in, & |
---|
77 | preldiff, phenry, pf0, pdensity, pdquer, & |
---|
78 | pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao |
---|
79 | |
---|
80 | pspecies=" " |
---|
81 | pdecay=-999.9 |
---|
82 | pweta=-9.9E-09 |
---|
83 | pwetb=0.0 |
---|
84 | pweta_in=-9.9E-09 |
---|
85 | pwetb_in=-9.9E-09 |
---|
86 | pwetc_in=-9.9E-09 |
---|
87 | pwetd_in=-9.9E-09 |
---|
88 | preldiff=-9.9 |
---|
89 | phenry=0.0 |
---|
90 | pf0=0.0 |
---|
91 | pdensity=-9.9E09 |
---|
92 | pdquer=0.0 |
---|
93 | pdsigma=0.0 |
---|
94 | pdryvel=-9.99 |
---|
95 | pohreact=-9.9E-09 |
---|
96 | pspec_ass=-9 |
---|
97 | pkao=-99.99 |
---|
98 | pweightmolar=-789.0 ! read failure indicator value |
---|
99 | |
---|
100 | ! Open the SPECIES file and read species names and properties |
---|
101 | !************************************************************ |
---|
102 | specnum(pos_spec)=id_spec |
---|
103 | write(aspecnumb,'(i3.3)') specnum(pos_spec) |
---|
104 | open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',form='formatted',err=998) |
---|
105 | !write(*,*) 'reading SPECIES',specnum(pos_spec) |
---|
106 | |
---|
107 | ASSSPEC=.FALSE. |
---|
108 | |
---|
109 | ! try namelist input |
---|
110 | read(unitspecies,species_params,iostat=readerror) |
---|
111 | close(unitspecies) |
---|
112 | |
---|
113 | if ((pweightmolar.eq.-789.0).or.(readerror.ne.0)) then ! no namelist found |
---|
114 | |
---|
115 | readerror=1 |
---|
116 | |
---|
117 | open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',err=998) |
---|
118 | |
---|
119 | do i=1,6 |
---|
120 | read(unitspecies,*) |
---|
121 | end do |
---|
122 | |
---|
123 | read(unitspecies,'(a10)',end=22) species(pos_spec) |
---|
124 | ! write(*,*) species(pos_spec) |
---|
125 | read(unitspecies,'(f18.1)',end=22) decay(pos_spec) |
---|
126 | ! write(*,*) decay(pos_spec) |
---|
127 | read(unitspecies,'(e18.1)',end=22) weta(pos_spec) |
---|
128 | ! write(*,*) weta(pos_spec) |
---|
129 | read(unitspecies,'(f18.2)',end=22) wetb(pos_spec) |
---|
130 | ! write(*,*) wetb(pos_spec) |
---|
131 | |
---|
132 | !*** NIK 31.01.2013: including in-cloud scavening parameters |
---|
133 | read(unitspecies,'(e18.1)',end=22) weta_in(pos_spec) |
---|
134 | ! write(*,*) weta_in(pos_spec) |
---|
135 | read(unitspecies,'(f18.2)',end=22) wetb_in(pos_spec) |
---|
136 | ! write(*,*) wetb_in(pos_spec) |
---|
137 | read(unitspecies,'(f18.2)',end=22) wetc_in(pos_spec) |
---|
138 | ! write(*,*) wetc_in(pos_spec) |
---|
139 | read(unitspecies,'(f18.2)',end=22) wetd_in(pos_spec) |
---|
140 | ! write(*,*) wetd_in(pos_spec) |
---|
141 | |
---|
142 | read(unitspecies,'(f18.1)',end=22) reldiff(pos_spec) |
---|
143 | ! write(*,*) reldiff(pos_spec) |
---|
144 | read(unitspecies,'(e18.1)',end=22) henry(pos_spec) |
---|
145 | ! write(*,*) henry(pos_spec) |
---|
146 | read(unitspecies,'(f18.1)',end=22) f0(pos_spec) |
---|
147 | ! write(*,*) f0(pos_spec) |
---|
148 | read(unitspecies,'(e18.1)',end=22) density(pos_spec) |
---|
149 | ! write(*,*) density(pos_spec) |
---|
150 | read(unitspecies,'(e18.1)',end=22) dquer(pos_spec) |
---|
151 | ! write(*,*) dquer(pos_spec) |
---|
152 | read(unitspecies,'(e18.1)',end=22) dsigma(pos_spec) |
---|
153 | ! write(*,*) dsigma(pos_spec) |
---|
154 | read(unitspecies,'(f18.2)',end=22) dryvel(pos_spec) |
---|
155 | ! write(*,*) dryvel(pos_spec) |
---|
156 | read(unitspecies,'(f18.2)',end=22) weightmolar(pos_spec) |
---|
157 | ! write(*,*) weightmolar(pos_spec) |
---|
158 | read(unitspecies,'(e18.1)',end=22) ohreact(pos_spec) |
---|
159 | ! write(*,*) ohreact(pos_spec) |
---|
160 | read(unitspecies,'(i18)',end=22) spec_ass(pos_spec) |
---|
161 | ! write(*,*) spec_ass(pos_spec) |
---|
162 | read(unitspecies,'(f18.2)',end=22) kao(pos_spec) |
---|
163 | ! write(*,*) kao(pos_spec) |
---|
164 | |
---|
165 | pspecies=species(pos_spec) |
---|
166 | pdecay=decay(pos_spec) |
---|
167 | pweta=weta(pos_spec) |
---|
168 | pwetb=wetb(pos_spec) |
---|
169 | pweta_in=weta_in(pos_spec) |
---|
170 | pwetb_in=wetb_in(pos_spec) |
---|
171 | pwetc_in=wetc_in(pos_spec) |
---|
172 | pwetd_in=wetd_in(pos_spec) |
---|
173 | preldiff=reldiff(pos_spec) |
---|
174 | phenry=henry(pos_spec) |
---|
175 | pf0=f0(pos_spec) |
---|
176 | pdensity=density(pos_spec) |
---|
177 | pdquer=dquer(pos_spec) |
---|
178 | pdsigma=dsigma(pos_spec) |
---|
179 | pdryvel=dryvel(pos_spec) |
---|
180 | pweightmolar=weightmolar(pos_spec) |
---|
181 | pohreact=ohreact(pos_spec) |
---|
182 | pspec_ass=spec_ass(pos_spec) |
---|
183 | pkao=kao(pos_spec) |
---|
184 | |
---|
185 | else |
---|
186 | |
---|
187 | species(pos_spec)=pspecies |
---|
188 | decay(pos_spec)=pdecay |
---|
189 | weta(pos_spec)=pweta |
---|
190 | wetb(pos_spec)=pwetb |
---|
191 | weta_in(pos_spec)=pweta_in |
---|
192 | wetb_in(pos_spec)=pwetb_in |
---|
193 | wetc_in(pos_spec)=pwetc_in |
---|
194 | wetd_in(pos_spec)=pwetd_in |
---|
195 | reldiff(pos_spec)=preldiff |
---|
196 | henry(pos_spec)=phenry |
---|
197 | f0(pos_spec)=pf0 |
---|
198 | density(pos_spec)=pdensity |
---|
199 | dquer(pos_spec)=pdquer |
---|
200 | dsigma(pos_spec)=pdsigma |
---|
201 | dryvel(pos_spec)=pdryvel |
---|
202 | weightmolar(pos_spec)=pweightmolar |
---|
203 | ohreact(pos_spec)=pohreact |
---|
204 | spec_ass(pos_spec)=pspec_ass |
---|
205 | kao(pos_spec)=pkao |
---|
206 | |
---|
207 | endif |
---|
208 | |
---|
209 | i=pos_spec |
---|
210 | |
---|
211 | if ((weta(pos_spec).gt.0).and.(henry(pos_spec).le.0)) then |
---|
212 | if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set |
---|
213 | endif |
---|
214 | |
---|
215 | if (spec_ass(pos_spec).gt.0) then |
---|
216 | spec_found=.FALSE. |
---|
217 | do j=1,pos_spec-1 |
---|
218 | if (spec_ass(pos_spec).eq.specnum(j)) then |
---|
219 | spec_ass(pos_spec)=j |
---|
220 | spec_found=.TRUE. |
---|
221 | ASSSPEC=.TRUE. |
---|
222 | endif |
---|
223 | end do |
---|
224 | if (spec_found.eqv..FALSE.) then |
---|
225 | goto 997 |
---|
226 | endif |
---|
227 | endif |
---|
228 | |
---|
229 | if (dsigma(i).eq.1.) dsigma(i)=1.0001 ! avoid floating exception |
---|
230 | if (dsigma(i).eq.0.) dsigma(i)=1.0001 ! avoid floating exception |
---|
231 | |
---|
232 | if ((reldiff(i).gt.0.).and.(density(i).gt.0.)) then |
---|
233 | write(*,*) '#### FLEXPART MODEL ERROR! FILE "SPECIES" ####' |
---|
234 | write(*,*) '#### IS CORRUPT. SPECIES CANNOT BE BOTH ####' |
---|
235 | write(*,*) '#### PARTICLE AND GAS. ####' |
---|
236 | write(*,*) '#### SPECIES NUMBER',aspecnumb |
---|
237 | stop |
---|
238 | endif |
---|
239 | 20 continue |
---|
240 | |
---|
241 | if (readerror.ne.0) then ! text format input |
---|
242 | |
---|
243 | ! Read in daily and day-of-week variation of emissions, if available |
---|
244 | !******************************************************************* |
---|
245 | ! HSO: This is not yet implemented as namelist parameters |
---|
246 | |
---|
247 | do j=1,24 ! initialize everything to no variation |
---|
248 | area_hour(i,j)=1. |
---|
249 | point_hour(i,j)=1. |
---|
250 | end do |
---|
251 | do j=1,7 |
---|
252 | area_dow(i,j)=1. |
---|
253 | point_dow(i,j)=1. |
---|
254 | end do |
---|
255 | |
---|
256 | read(unitspecies,*,end=22) |
---|
257 | do j=1,24 ! 24 hours, starting with 0-1 local time |
---|
258 | read(unitspecies,*) ihour,area_hour(i,j),point_hour(i,j) |
---|
259 | end do |
---|
260 | read(unitspecies,*) |
---|
261 | do j=1,7 ! 7 days of the week, starting with Monday |
---|
262 | read(unitspecies,*) idow,area_dow(i,j),point_dow(i,j) |
---|
263 | end do |
---|
264 | |
---|
265 | endif |
---|
266 | |
---|
267 | 22 close(unitspecies) |
---|
268 | |
---|
269 | ! namelist output if requested |
---|
270 | if (nmlout.eqv..true.) then |
---|
271 | open(unitspecies,file=path(2)(1:length(2))//'SPECIES_'//aspecnumb//'.namelist',access='append',status='new',err=1000) |
---|
272 | write(unitspecies,nml=species_params) |
---|
273 | close(unitspecies) |
---|
274 | endif |
---|
275 | |
---|
276 | return |
---|
277 | |
---|
278 | 996 write(*,*) '#####################################################' |
---|
279 | write(*,*) '#### FLEXPART MODEL ERROR! #### ' |
---|
280 | write(*,*) '#### WET DEPOSITION SWITCHED ON, BUT NO HENRYS #### ' |
---|
281 | write(*,*) '#### CONSTANT IS SET ####' |
---|
282 | write(*,*) '#### PLEASE MODIFY SPECIES DESCR. FILE! #### ' |
---|
283 | write(*,*) '#####################################################' |
---|
284 | stop |
---|
285 | |
---|
286 | |
---|
287 | 997 write(*,*) '#####################################################' |
---|
288 | write(*,*) '#### FLEXPART MODEL ERROR! #### ' |
---|
289 | write(*,*) '#### THE ASSSOCIATED SPECIES HAS TO BE DEFINED #### ' |
---|
290 | write(*,*) '#### BEFORE THE ONE WHICH POINTS AT IT #### ' |
---|
291 | write(*,*) '#### PLEASE CHANGE ORDER IN RELEASES OR ADD #### ' |
---|
292 | write(*,*) '#### THE ASSOCIATED SPECIES IN RELEASES #### ' |
---|
293 | write(*,*) '#####################################################' |
---|
294 | stop |
---|
295 | |
---|
296 | |
---|
297 | 998 write(*,*) '#####################################################' |
---|
298 | write(*,*) '#### FLEXPART MODEL ERROR! #### ' |
---|
299 | write(*,*) '#### THE SPECIES FILE FOR SPECIES ', id_spec |
---|
300 | write(*,*) '#### CANNOT BE FOUND: CREATE FILE' |
---|
301 | write(*,*) '#### ',path(1)(1:length(1)),'SPECIES/SPECIES_',aspecnumb |
---|
302 | write(*,*) '#####################################################' |
---|
303 | stop |
---|
304 | |
---|
305 | 1000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "SPECIES_',aspecnumb,'.namelist' |
---|
306 | write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY #### ' |
---|
307 | write(*,'(a)') path(2)(1:length(2)) |
---|
308 | stop |
---|
309 | |
---|
310 | end subroutine readspecies |
---|