source: flexpart.git/src/readspecies.f90 @ 341f4b7

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 341f4b7 was 341f4b7, checked in by Espen Sollum ATMOS <eso@…>, 8 years ago

SPECIES files converted to namelist format. Fixed-format SPCIES files renamed with .oldformat extension. Added 2 wet depo parameters to old-format SPECIES. Renamed internal variables and parameters used for wet deposition. incloud_ratio increased to 2.2

  • Property mode set to 100644
File size: 15.8 KB
Line 
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
22subroutine 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_gas, wetb_gas   Parameters for determining below-cloud scavenging     *
45  ! ccn_aero              Parameter for determining in-cloud scavenging         *
46  ! in_aero              Parameter for determining in-cloud scavenging         *
47  ! ohcconst             OH reaction rate constant C                           *
48  ! ohdconst             OH reaction rate constant D                           *
49  ! ohnconst             OH reaction rate constant n                           *
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_gas, pwetb_gas, preldiff, phenry, pf0, pdensity, pdquer
69  real :: pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, pspec_ass, pkao
70  real :: pcrain_aero, pcsnow_aero, pccn_aero, pin_aero
71  integer :: readerror
72
73! declare namelist
74  namelist /species_params/ &
75       pspecies, pdecay, pweta_gas, pwetb_gas, &
76       pcrain_aero, pcsnow_aero, pccn_aero, pin_aero, &
77       preldiff, phenry, pf0, pdensity, pdquer, &
78       pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, pspec_ass, pkao
79
80  pspecies="" ! read failure indicator value
81  pdecay=-999.9
82  pweta_gas=-9.9E-09
83  pwetb_gas=0.0
84  pcrain_aero=-9.9E-09
85  pcsnow_aero=-9.9E-09
86  pccn_aero=-9.9E-09
87  pin_aero=-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  pohcconst=-9.99
96  pohdconst=-9.9E-09
97  pohnconst=2.0
98  pspec_ass=-9
99  pkao=-99.99
100  pweightmolar=-999.9
101
102! Open the SPECIES file and read species names and properties
103!************************************************************
104  specnum(pos_spec)=id_spec
105  write(aspecnumb,'(i3.3)') specnum(pos_spec)
106  open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',form='formatted',err=998)
107!write(*,*) 'reading SPECIES',specnum(pos_spec)
108
109  ASSSPEC=.FALSE.
110
111! try namelist input
112  read(unitspecies,species_params,iostat=readerror)
113  close(unitspecies)
114
115!  if ((pweightmolar.eq.-789.0).or.(readerror.ne.0)) then ! no namelist found
116  if ((len(pspecies).eq.0).or.(readerror.ne.0)) then ! no namelist found
117
118    readerror=1
119
120    open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',err=998)
121
122    do i=1,6
123      read(unitspecies,*)
124    end do
125
126    read(unitspecies,'(a10)',end=22) species(pos_spec)
127!  write(*,*) species(pos_spec)
128    read(unitspecies,'(f18.1)',end=22) decay(pos_spec)
129!  write(*,*) decay(pos_spec)
130    read(unitspecies,'(e18.1)',end=22) weta_gas(pos_spec)
131!  write(*,*) weta_gas(pos_spec)
132    read(unitspecies,'(f18.2)',end=22) wetb_gas(pos_spec)
133!  write(*,*) wetb_gas(pos_spec)
134    read(unitspecies,'(e18.1)',end=22) crain_aero(pos_spec)
135!  write(*,*) crain_aero(pos_spec)
136    read(unitspecies,'(f18.2)',end=22) csnow_aero(pos_spec)
137!  write(*,*) csnow_aero(pos_spec)
138!*** NIK 31.01.2013: including in-cloud scavening parameters
139    read(unitspecies,'(e18.1)',end=22) ccn_aero(pos_spec)
140!  write(*,*) ccn_aero(pos_spec)
141    read(unitspecies,'(f18.2)',end=22) in_aero(pos_spec)
142!  write(*,*) in_aero(pos_spec)
143    read(unitspecies,'(f18.1)',end=22) reldiff(pos_spec)
144!  write(*,*) reldiff(pos_spec)
145    read(unitspecies,'(e18.1)',end=22) henry(pos_spec)
146!  write(*,*) henry(pos_spec)
147    read(unitspecies,'(f18.1)',end=22) f0(pos_spec)
148!  write(*,*) f0(pos_spec)
149    read(unitspecies,'(e18.1)',end=22) density(pos_spec)
150!  write(*,*) density(pos_spec)
151    read(unitspecies,'(e18.1)',end=22) dquer(pos_spec)
152!    write(*,*) 'dquer(pos_spec):', dquer(pos_spec)
153    read(unitspecies,'(e18.1)',end=22) dsigma(pos_spec)
154!  write(*,*) dsigma(pos_spec)
155    read(unitspecies,'(f18.2)',end=22) dryvel(pos_spec)
156!  write(*,*) dryvel(pos_spec)
157    read(unitspecies,'(f18.2)',end=22) weightmolar(pos_spec)
158!  write(*,*) weightmolar(pos_spec)
159    read(unitspecies,'(e18.2)',end=22) ohcconst(pos_spec)
160!  write(*,*) ohcconst(pos_spec)
161    read(unitspecies,'(f8.2)',end=22) ohdconst(pos_spec)
162!  write(*,*) ohdconst(pos_spec)
163    read(unitspecies,'(f8.2)',end=22) ohnconst(pos_spec)
164!  write(*,*) ohnconst(pos_spec)
165    read(unitspecies,'(i18)',end=22) spec_ass(pos_spec)
166!  write(*,*) spec_ass(pos_spec)
167    read(unitspecies,'(f18.2)',end=22) kao(pos_spec)
168!       write(*,*) kao(pos_spec)
169
170    pspecies=species(pos_spec)
171    pdecay=decay(pos_spec)
172    pweta_gas=weta_gas(pos_spec)
173    pwetb_gas=wetb_gas(pos_spec)
174    pcrain_aero=crain_aero(pos_spec)
175    pcsnow_aero=csnow_aero(pos_spec)
176    pccn_aero=ccn_aero(pos_spec)
177    pin_aero=in_aero(pos_spec)
178    preldiff=reldiff(pos_spec)
179    phenry=henry(pos_spec)
180    pf0=f0(pos_spec)
181    pdensity=density(pos_spec)
182    pdquer=dquer(pos_spec)
183    pdsigma=dsigma(pos_spec)
184    pdryvel=dryvel(pos_spec)
185    pweightmolar=weightmolar(pos_spec)
186    pohcconst=ohcconst(pos_spec)
187    pohdconst=ohdconst(pos_spec)
188    pohnconst=ohnconst(pos_spec)
189    pspec_ass=spec_ass(pos_spec)
190    pkao=kao(pos_spec)
191
192  else
193
194    species(pos_spec)=pspecies
195    decay(pos_spec)=pdecay
196    weta_gas(pos_spec)=pweta_gas
197    wetb_gas(pos_spec)=pwetb_gas
198    crain_aero=pcrain_aero
199    csnow_aero=pcsnow_aero
200    ccn_aero(pos_spec)=pccn_aero
201    in_aero(pos_spec)=pin_aero
202    reldiff(pos_spec)=preldiff
203    henry(pos_spec)=phenry
204    f0(pos_spec)=pf0
205    density(pos_spec)=pdensity
206    dquer(pos_spec)=pdquer
207    dsigma(pos_spec)=pdsigma
208    dryvel(pos_spec)=pdryvel
209    weightmolar(pos_spec)=pweightmolar
210    ohcconst(pos_spec)=pohcconst
211    ohdconst(pos_spec)=pohdconst
212    ohnconst(pos_spec)=pohnconst
213    spec_ass(pos_spec)=pspec_ass
214    kao(pos_spec)=pkao
215
216  endif
217
218  i=pos_spec
219
220!NIK 16.02.2015
221! Check scavenging parameters given in SPECIES file
222
223  if (weta_gas(pos_spec).gt.0.0 .or. wetb_gas(pos_spec).gt.0.0 .or. ccn_aero(pos_spec).gt.0.0 .or. in_aero(pos_spec).gt.0.0) then
224
225  if (dquer(pos_spec).gt.0) then !is particle
226    if (lroot) then
227      write(*,'(a,f5.2)') '  Particle below-cloud scavenging parameter A &
228           &(Rain collection efficiency)  ', crain_aero(pos_spec)
229      write(*,'(a,f5.2)') '  Particle below-cloud scavenging parameter B &
230           &(Snow collection efficiency)  ', csnow_aero(pos_spec)
231    end if
232    if (weta_gas(pos_spec).gt.1.0 .or. wetb_gas(pos_spec).gt.1.0) then
233      if (lroot) then
234        write(*,*) '*******************************************'
235        write(*,*) ' WARNING: Particle below-cloud scavenging parameter A or B &
236             &is out of likely range'
237        write(*,*) '          Likely range is 0.0-1.0'
238        write(*,*) '*******************************************'
239      end if
240    endif
241    if (lroot) then
242      write(*,'(a,f5.2)') '  Particle in-cloud scavenging parameter Ai &
243           &(CCN efficiency)  ', ccn_aero(pos_spec)
244      write(*,'(a,f5.2)') '  Particle in-cloud scavenging parameter Bi &
245           &(IN efficiency)  ', in_aero(pos_spec)
246    end if
247    if (ccn_aero(pos_spec).gt.1.0 .or. ccn_aero(pos_spec).lt.0.01) then
248      if (lroot) then
249        write(*,*) '*******************************************'
250        write(*,*) ' WARNING: Particle in-cloud scavenging parameter A is out of likely range'
251        write(*,*) '          Likely range is 0.0-1.0 for CCN '
252        write(*,*) '*******************************************'
253      end if
254    endif
255    if (in_aero(pos_spec).gt.1.0 .or. in_aero(pos_spec).lt.0.01) then
256      if (lroot) then
257        write(*,*) '*******************************************'
258        write(*,*) ' WARNING: Particle in-cloud scavenging parameter B is out of likely range'
259        write(*,*) '          Likely range is 0.0-1.0 for Ice nuclei (IN) '
260        write(*,*) '*******************************************'
261      end if
262    endif
263
264  else !is gas
265    if (lroot) then
266      write(*,*) '  Gas below-cloud scavenging parameter A  ', weta_gas(pos_spec)
267      write(*,'(a,f5.2)') '  Gas below-cloud scavenging parameter B  ', wetb_gas(pos_spec)
268      write(*,*) ' Gas in-cloud scavenging uses default values as in Hertel et al 1995'
269    end if
270    if (weta_gas(pos_spec).gt.0.) then !if wet deposition is turned on
271      if (weta_gas(pos_spec).gt.1E-04 .or. weta_gas(pos_spec).lt.1E-09) then
272        if (lroot) then
273          write(*,*) '*******************************************'
274          write(*,*) ' WARNING: Gas below-cloud scavenging parameter A is out of likely range'
275          write(*,*) '          Likely range is 1E-04 to 1E-08 (see Hertel et al 1995)'
276          write(*,*) '*******************************************'
277        end if
278      endif
279    end if
280    if (wetb_gas(pos_spec).gt.0.) then !if wet deposition is turned on
281      if (wetb_gas(pos_spec).gt.0.8 .or. wetb_gas(pos_spec).lt.0.6) then
282        if (lroot) then
283          write(*,*) '*******************************************'
284          write(*,*) ' WARNING: Gas below-cloud scavenging parameter B is out of likely range'
285          write(*,*) '          Likely range is 0.6 to 0.8 (see Hertel et al 1995)'
286          write(*,*) '*******************************************'
287        end if
288      endif
289    end if
290  endif
291  endif
292
293  if (((weta_gas(pos_spec).gt.0).or.(wetb_gas(pos_spec).gt.0)).and.(henry(pos_spec).le.0)) then
294    if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set
295  endif
296
297  if (spec_ass(pos_spec).gt.0) then
298    spec_found=.FALSE.
299    do j=1,pos_spec-1
300      if (spec_ass(pos_spec).eq.specnum(j)) then
301        spec_ass(pos_spec)=j
302        spec_found=.TRUE.
303        ASSSPEC=.TRUE.
304      endif
305    end do
306    if (spec_found.eqv..FALSE.) then
307      goto 997
308    endif
309  endif
310
311  if (dsigma(i).eq.1.) dsigma(i)=1.0001   ! avoid floating exception
312  if (dsigma(i).eq.0.) dsigma(i)=1.0001   ! avoid floating exception
313
314  if ((reldiff(i).gt.0.).and.(density(i).gt.0.)) then
315    write(*,*) '#### FLEXPART MODEL ERROR! FILE "SPECIES"    ####'
316    write(*,*) '#### IS CORRUPT. SPECIES CANNOT BE BOTH      ####'
317    write(*,*) '#### PARTICLE AND GAS.                       ####'
318    write(*,*) '#### SPECIES NUMBER',aspecnumb
319    stop
320  endif
32120 continue
322
323
324! Read in daily and day-of-week variation of emissions, if available
325!*******************************************************************
326! HSO: This is not yet implemented as namelist parameters
327
328  do j=1,24           ! initialize everything to no variation
329    area_hour(i,j)=1.
330    point_hour(i,j)=1.
331  end do
332  do j=1,7
333    area_dow(i,j)=1.
334    point_dow(i,j)=1.
335  end do
336
337  if (readerror.ne.0) then ! text format input
338
339    read(unitspecies,*,end=22)
340    do j=1,24     ! 24 hours, starting with 0-1 local time
341      read(unitspecies,*) ihour,area_hour(i,j),point_hour(i,j)
342    end do
343    read(unitspecies,*)
344    do j=1,7      ! 7 days of the week, starting with Monday
345      read(unitspecies,*) idow,area_dow(i,j),point_dow(i,j)
346    end do
347
348  endif
349
35022 close(unitspecies)
351
352! namelist output if requested
353  if (nmlout.and.lroot) then
354    open(unitspecies,file=path(2)(1:length(2))//'SPECIES_'//aspecnumb//'.namelist',access='append',status='replace',err=1000)
355    write(unitspecies,nml=species_params)
356    close(unitspecies)
357  endif
358
359  return
360
361996 write(*,*) '#####################################################'
362  write(*,*) '#### FLEXPART MODEL ERROR!                      #### '
363  write(*,*) '#### WET DEPOSITION SWITCHED ON, BUT NO HENRYS  #### '
364  write(*,*) '#### CONSTANT IS SET                            ####'
365  write(*,*) '#### PLEASE MODIFY SPECIES DESCR. FILE!        #### '
366  write(*,*) '#####################################################'
367  stop
368
369
370997 write(*,*) '#####################################################'
371  write(*,*) '#### FLEXPART MODEL ERROR!                      #### '
372  write(*,*) '#### THE ASSSOCIATED SPECIES HAS TO BE DEFINED  #### '
373  write(*,*) '#### BEFORE THE ONE WHICH POINTS AT IT          #### '
374  write(*,*) '#### PLEASE CHANGE ORDER IN RELEASES OR ADD     #### '
375  write(*,*) '#### THE ASSOCIATED SPECIES IN RELEASES         #### '
376  write(*,*) '#####################################################'
377  stop
378
379
380998 write(*,*) '#####################################################'
381  write(*,*) '#### FLEXPART MODEL ERROR!                      #### '
382  write(*,*) '#### THE SPECIES FILE FOR SPECIES ', id_spec
383  write(*,*) '#### CANNOT BE FOUND: CREATE FILE'
384  write(*,*) '#### ',path(1)(1:length(1)),'SPECIES/SPECIES_',aspecnumb
385  write(*,*) '#####################################################'
386  stop
387
3881000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "SPECIES_',aspecnumb,'.namelist'
389  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
390  write(*,'(a)') path(2)(1:length(2))
391  stop
392
393end subroutine readspecies
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG