source: flexpart.git/src/readspecies.f90 @ 7999df47

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

More informative logging output (by NIK)

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