source: branches/flexpart91_hasod/src_parallel/readspecies.f90

Last change on this file was 10, checked in by hasod, 11 years ago

ADD: namelist input implemented for all common input files

File size: 8.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  !   HSO, 13 August 2013
34  !   added optional namelist input
35  !                                                                            *
36  !*****************************************************************************
37  !                                                                            *
38  ! Variables:                                                                 *
39  ! decaytime(maxtable)  half time for radiological decay                      *
40  ! specname(maxtable)   names of chemical species, radionuclides              *
41  ! wetscava, wetscavb   Parameters for determining scavenging coefficient     *
42  ! ohreact              OH reaction rate                                      *
43  ! id_spec              SPECIES number as referenced in RELEASE file          *
44  ! id_pos               position where SPECIES data shall be stored           *
45  !                                                                            *
46  ! Constants:                                                                 *
47  !                                                                            *
48  !*****************************************************************************
49
50  use par_mod
51  use com_mod
52
53  implicit none
54
55  integer :: i, pos_spec,j
56  integer :: idow,ihour,id_spec
57  character(len=3) :: aspecnumb
58  logical :: spec_found
59
60  character(len=16) :: pspecies
61  real :: pdecay, pweta, pwetb, preldiff, phenry, pf0, pdensity, pdquer
62  real :: pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao
63  integer :: readerror
64
65  ! declare namelist
66  namelist /species_params/ &
67   pspecies, pdecay, pweta, pwetb, preldiff, phenry, pf0, pdensity, pdquer, &
68   pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao
69
70  pspecies=" "
71  pdecay=-999.9
72  pweta=-9.9E-09
73  pwetb=0.0
74  preldiff=-9.9
75  phenry=0.0
76  pf0=0.0
77  pdensity=-9.9E09
78  pdquer=0.0
79  pdsigma=0.0
80  pdryvel=-9.99
81  pohreact=-9.9E-09
82  pspec_ass=-9
83  pkao=-99.99
84  pweightmolar=-789.0 ! read failure indicator value
85
86  ! Open the SPECIES file and read species names and properties
87  !************************************************************
88  specnum(pos_spec)=id_spec
89  write(aspecnumb,'(i3.3)') specnum(pos_spec)
90  open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',err=998)
91  write(*,*) 'reading SPECIES',specnum(pos_spec)
92
93  ASSSPEC=.FALSE.
94
95  ! try namelist input
96  read(unitspecies,species_params,iostat=readerror)
97   
98  if ((pweightmolar.eq.-789.0).or.(readerror.ne.0)) then ! no namelist found
99
100    rewind(unitspecies)
101
102    do i=1,6
103      read(unitspecies,*)
104    end do
105
106    read(unitspecies,'(a10)',end=22) species(pos_spec)
107    read(unitspecies,'(f18.1)',end=22) decay(pos_spec)
108    read(unitspecies,'(e18.1)',end=22) weta(pos_spec)
109    read(unitspecies,'(f18.2)',end=22) wetb(pos_spec)
110    read(unitspecies,'(f18.1)',end=22) reldiff(pos_spec)
111    read(unitspecies,'(e18.1)',end=22) henry(pos_spec)
112    read(unitspecies,'(f18.1)',end=22) f0(pos_spec)
113    read(unitspecies,'(e18.1)',end=22) density(pos_spec)
114    read(unitspecies,'(e18.1)',end=22) dquer(pos_spec)
115    read(unitspecies,'(e18.1)',end=22) dsigma(pos_spec)
116    read(unitspecies,'(f18.2)',end=22) dryvel(pos_spec)
117    read(unitspecies,'(f18.2)',end=22) weightmolar(pos_spec)
118    read(unitspecies,'(e18.1)',end=22) ohreact(pos_spec)
119    read(unitspecies,'(i18)',end=22) spec_ass(pos_spec)
120    read(unitspecies,'(f18.2)',end=22) kao(pos_spec)
121
122  else
123
124    species(pos_spec)=pspecies
125    decay(pos_spec)=pdecay
126    weta(pos_spec)=pweta
127    wetb(pos_spec)=pwetb
128    reldiff(pos_spec)=preldiff
129    henry(pos_spec)=phenry
130    f0(pos_spec)=pf0
131    density(pos_spec)=pdensity
132    dquer(pos_spec)=pdquer
133    dsigma(pos_spec)=pdsigma
134    dryvel(pos_spec)=pdryvel
135    weightmolar(pos_spec)=pweightmolar
136    ohreact(pos_spec)=pohreact
137    spec_ass(pos_spec)=pspec_ass
138    kao(pos_spec)=pkao
139
140  endif
141
142  i=pos_spec
143
144  if ((weta(pos_spec).gt.0).and.(henry(pos_spec).le.0)) then
145     if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set
146  endif
147
148  if (spec_ass(pos_spec).gt.0) then
149     spec_found=.FALSE.
150     do j=1,pos_spec-1
151        if (spec_ass(pos_spec).eq.specnum(j)) then
152           spec_ass(pos_spec)=j
153           spec_found=.TRUE.
154           ASSSPEC=.TRUE.
155        endif
156     end do
157     if (spec_found.eqv..FALSE.) then
158        goto 997
159     endif
160  endif
161
162  if (dsigma(i).eq.1.) dsigma(i)=1.0001   ! avoid floating exception
163  if (dsigma(i).eq.0.) dsigma(i)=1.0001   ! avoid floating exception
164
165  if ((reldiff(i).gt.0.).and.(density(i).gt.0.)) then
166    write(*,*) '#### FLEXPART MODEL ERROR! FILE "SPECIES"    ####'
167    write(*,*) '#### IS CORRUPT. SPECIES CANNOT BE BOTH      ####'
168    write(*,*) '#### PARTICLE AND GAS.                       ####'
169    write(*,*) '#### SPECIES NUMBER',aspecnumb
170    stop
171  endif
17220   continue
173
174
175  ! Read in daily and day-of-week variation of emissions, if available
176  !*******************************************************************
177
178    do j=1,24           ! initialize everything to no variation
179      area_hour(i,j)=1.
180      point_hour(i,j)=1.
181    end do
182    do j=1,7
183      area_dow(i,j)=1.
184      point_dow(i,j)=1.
185    end do
186
187    read(unitspecies,*,end=22)
188    do j=1,24     ! 24 hours, starting with 0-1 local time
189      read(unitspecies,*) ihour,area_hour(i,j),point_hour(i,j)
190    end do
191    read(unitspecies,*)
192    do j=1,7      ! 7 days of the week, starting with Monday
193      read(unitspecies,*) idow,area_dow(i,j),point_dow(i,j)
194    end do
195
19622   close(unitspecies)
197
198   return
199
200996   write(*,*) '#####################################################'
201  write(*,*) '#### FLEXPART MODEL ERROR!                      #### '
202  write(*,*) '#### WET DEPOSITION SWITCHED ON, BUT NO HENRYS  #### '
203  write(*,*) '#### CONSTANT IS SET                            ####'
204  write(*,*) '#### PLEASE MODIFY SPECIES DESCR. FILE!        #### '
205  write(*,*) '#####################################################'
206  stop
207
208
209997   write(*,*) '#####################################################'
210  write(*,*) '#### FLEXPART MODEL ERROR!                      #### '
211  write(*,*) '#### THE ASSSOCIATED SPECIES HAS TO BE DEFINED  #### '
212  write(*,*) '#### BEFORE THE ONE WHICH POINTS AT IT          #### '
213  write(*,*) '#### PLEASE CHANGE ORDER IN RELEASES OR ADD     #### '
214  write(*,*) '#### THE ASSOCIATED SPECIES IN RELEASES         #### '
215  write(*,*) '#####################################################'
216  stop
217
218
219998   write(*,*) '#####################################################'
220  write(*,*) '#### FLEXPART MODEL ERROR!                      #### '
221  write(*,*) '#### THE SPECIES FILE FOR SPECIES ', id_spec
222  write(*,*) '#### CANNOT BE FOUND: CREATE FILE'
223  write(*,*) '#### ',path(1)(1:length(1)),'SPECIES/SPECIES_',aspecnumb
224  write(*,*) '#####################################################'
225  stop
226
227
228end subroutine readspecies
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG