!********************************************************************** ! Copyright 1998-2015 * ! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa, * ! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann * ! * ! This file is part of FLEXPART. * ! * ! FLEXPART is free software: you can redistribute it and/or modify * ! it under the terms of the GNU General Public License as published by* ! the Free Software Foundation, either version 3 of the License, or * ! (at your option) any later version. * ! * ! FLEXPART is distributed in the hope that it will be useful, * ! but WITHOUT ANY WARRANTY; without even the implied warranty of * ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * ! GNU General Public License for more details. * ! * ! You should have received a copy of the GNU General Public License * ! along with FLEXPART. If not, see . * !********************************************************************** subroutine readspecies(id_spec,id_pos) !***************************************************************************** ! * ! This routine reads names and physical constants of chemical species/ * ! radionuclides given in the parameter id_pos * ! * ! Author: A. Stohl * ! * ! 11 July 1996 * ! ! Changes: * ! * ! N. Kristiansen, 31.01.2013: Including parameters for in-cloud scavenging * ! * ! HSO, 13 August 2013: added optional namelist input ! PS, 2/2015: access= -> position= ! PS, 4/2015: quick fix for bug associated with end=22 ! * !***************************************************************************** ! * ! Variables: * ! decaytime(maxtable) half time for radiological decay * ! specname(maxtable) names of chemical species, radionuclides * ! weta, wetb Parameters for determining below-cloud scavenging * ! weta_in Parameter for determining in-cloud scavenging * ! wetb_in Parameter for determining in-cloud scavenging * ! wetc_in Parameter for determining in-cloud scavenging * ! wetd_in Parameter for determining in-cloud scavenging * ! ohreact OH reaction rate * ! id_spec SPECIES number as referenced in RELEASE file * ! id_pos position where SPECIES data shall be stored * ! * ! Constants: * ! * !***************************************************************************** use par_mod use com_mod implicit none integer :: i, id_pos,j integer :: idow,ihour,id_spec character(len=3) :: aspecnumb logical :: spec_found character(len=16) :: pspecies real :: pdecay, pweta, pwetb, preldiff, phenry, pf0, pdensity, pdquer real :: pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao real :: pweta_in, pwetb_in, pwetc_in, pwetd_in integer :: ios ! declare namelist namelist /species_params/ & pspecies, pdecay, pweta, pwetb, & pweta_in, pwetb_in, pwetc_in, pwetd_in, & preldiff, phenry, pf0, pdensity, pdquer, & pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao pspecies=" " pdecay=-999.9 pweta=-9.9E-09 pwetb=0.0 pweta_in=-9.9E-09 pwetb_in=-9.9E-09 pwetc_in=-9.9E-09 pwetd_in=-9.9E-09 preldiff=-9.9 phenry=0.0 pf0=0.0 pdensity=-9.9E09 pdquer=0.0 pdsigma=0.0 pdryvel=-9.99 pohreact=-9.9E-09 pspec_ass=-9 pkao=-99.99 pweightmolar=-789.0 ! read failure indicator value ! Open the SPECIES file and read species names and properties !************************************************************ specnum(id_pos)=id_spec write(aspecnumb,'(i3.3)') specnum(id_pos) open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',form='formatted',err=998) !write(*,*) 'reading SPECIES',specnum(id_pos) ASSSPEC=.FALSE. ! try namelist input read(unitspecies,species_params,iostat=ios) close(unitspecies) if ((pweightmolar.eq.-789.0).or.(ios.ne.0)) then ! no namelist found open(unitspecies,file=path(1) (1:length(1))//'SPECIES/SPECIES_'//aspecnumb, status='old', err=998) do i=1,6 read(unitspecies,*) end do read(unitspecies,'(a10)',end=20) species(id_pos) ! write(*,*) species(id_pos) read(unitspecies,'(f18.1)',end=20) decay(id_pos) ! write(*,*) decay(id_pos) read(unitspecies,'(e18.1)',end=20) weta(id_pos) ! write(*,*) weta(id_pos) read(unitspecies,'(f18.2)',end=20) wetb(id_pos) ! write(*,*) wetb(id_pos) !*** NIK 31.01.2013: including in-cloud scavening parameters read(unitspecies,'(e18.1)',end=20) weta_in(id_pos) ! write(*,*) weta_in(id_pos) read(unitspecies,'(f18.2)',end=20) wetb_in(id_pos) ! write(*,*) wetb_in(id_pos) read(unitspecies,'(f18.2)',end=20) wetc_in(id_pos) ! write(*,*) wetc_in(id_pos) read(unitspecies,'(f18.2)',end=20) wetd_in(id_pos) ! write(*,*) wetd_in(id_pos) read(unitspecies,'(f18.1)',end=20) reldiff(id_pos) ! write(*,*) reldiff(id_pos) read(unitspecies,'(e18.1)',end=20) henry(id_pos) ! write(*,*) henry(id_pos) read(unitspecies,'(f18.1)',end=20) f0(id_pos) ! write(*,*) f0(id_pos) read(unitspecies,'(e18.1)',end=20) density(id_pos) ! write(*,*) density(id_pos) read(unitspecies,'(e18.1)',end=20) dquer(id_pos) ! write(*,*) dquer(id_pos) read(unitspecies,'(e18.1)',end=20) dsigma(id_pos) ! write(*,*) dsigma(id_pos) read(unitspecies,'(f18.2)',end=20) dryvel(id_pos) ! write(*,*) dryvel(id_pos) read(unitspecies,'(f18.2)',end=20) weightmolar(id_pos) ! write(*,*) weightmolar(id_pos) read(unitspecies,'(e18.1)',end=20) ohreact(id_pos) ! write(*,*) ohreact(id_pos) read(unitspecies,'(i18)',end=20) spec_ass(id_pos) ! write(*,*) spec_ass(id_pos) read(unitspecies,'(f18.2)',end=20) kao(id_pos) ! write(*,*) kao(id_pos) pspecies=species(id_pos) pdecay=decay(id_pos) pweta=weta(id_pos) pwetb=wetb(id_pos) pweta_in=weta_in(id_pos) pwetb_in=wetb_in(id_pos) pwetc_in=wetc_in(id_pos) pwetd_in=wetd_in(id_pos) preldiff=reldiff(id_pos) phenry=henry(id_pos) pf0=f0(id_pos) pdensity=density(id_pos) pdquer=dquer(id_pos) pdsigma=dsigma(id_pos) pdryvel=dryvel(id_pos) pweightmolar=weightmolar(id_pos) pohreact=ohreact(id_pos) pspec_ass=spec_ass(id_pos) pkao=kao(id_pos) else species(id_pos)=pspecies decay(id_pos)=pdecay weta(id_pos)=pweta wetb(id_pos)=pwetb weta_in(id_pos)=pweta_in wetb_in(id_pos)=pwetb_in wetc_in(id_pos)=pwetc_in wetd_in(id_pos)=pwetd_in reldiff(id_pos)=preldiff henry(id_pos)=phenry f0(id_pos)=pf0 density(id_pos)=pdensity dquer(id_pos)=pdquer dsigma(id_pos)=pdsigma dryvel(id_pos)=pdryvel weightmolar(id_pos)=pweightmolar ohreact(id_pos)=pohreact spec_ass(id_pos)=pspec_ass kao(id_pos)=pkao endif if ((weta(id_pos).gt.0).and.(henry(id_pos).le.0)) then if (dquer(id_pos).le.0) goto 996 ! no particle, no henry set endif if (spec_ass(id_pos).gt.0) then spec_found=.FALSE. do j=1,id_pos-1 if (spec_ass(id_pos).eq.specnum(j)) then spec_ass(id_pos)=j spec_found=.TRUE. ASSSPEC=.TRUE. endif end do if (spec_found.eqv..FALSE.) then goto 997 endif endif if (dsigma(id_pos).eq.1.) dsigma(id_pos)=1.0001 ! avoid floating exception if (dsigma(id_pos).eq.0.) dsigma(id_pos)=1.0001 ! avoid floating exception if ((reldiff(id_pos).gt.0.).and.(density(id_pos).gt.0.)) then write(*,*) '#### FLEXPART MODEL ERROR! FILE "SPECIES" ####' write(*,*) '#### IS CORRUPT. SPECIES CANNOT BE BOTH ####' write(*,*) '#### PARTICLE AND GAS. ####' write(*,*) '#### SPECIES NUMBER',aspecnumb stop endif 20 continue ! Read in daily and day-of-week variation of emissions, if available !******************************************************************* ! HSO: This is not yet implemented as namelist parameters ! default values set to 1 do j=1,24 ! initialize everything to no variation area_hour(id_pos,j)=1. point_hour(id_pos,j)=1. end do do j=1,7 area_dow(id_pos,j)=1. point_dow(id_pos,j)=1. end do if (ios.ne.0) then ! text format input read(unitspecies,*,iostat=ios) if (ios .ne. 0) goto 22 ! ifort does not like err= do j=1,24 ! 24 hours, starting with 0-1 local time read(unitspecies,*) ihour,area_hour(id_pos,j),point_hour(id_pos,j) end do read(unitspecies,*) do j=1,7 ! 7 days of the week, starting with Monday read(unitspecies,*) idow,area_dow(id_pos,j),point_dow(id_pos,j) end do endif 22 close(unitspecies) ! namelist output if requested if (nmlout.eqv..true.) then open(unitspecies,file=path(2)(1:length(2))//'SPECIES_'//aspecnumb//'.namelist',position='append',status='new',err=1000) write(unitspecies,nml=species_params) close(unitspecies) endif return 996 write(*,*) '#####################################################' write(*,*) '#### FLEXPART MODEL ERROR! #### ' write(*,*) '#### WET DEPOSITION SWITCHED ON, BUT NO HENRYS #### ' write(*,*) '#### CONSTANT IS SET ####' write(*,*) '#### PLEASE MODIFY SPECIES DESCR. FILE! #### ' write(*,*) '#####################################################' stop 997 write(*,*) '#####################################################' write(*,*) '#### FLEXPART MODEL ERROR! #### ' write(*,*) '#### THE ASSSOCIATED SPECIES HAS TO BE DEFINED #### ' write(*,*) '#### BEFORE THE ONE WHICH POINTS AT IT #### ' write(*,*) '#### PLEASE CHANGE ORDER IN RELEASES OR ADD #### ' write(*,*) '#### THE ASSOCIATED SPECIES IN RELEASES #### ' write(*,*) '#####################################################' stop 998 write(*,*) '#####################################################' write(*,*) '#### FLEXPART MODEL ERROR! #### ' write(*,*) '#### THE SPECIES FILE FOR SPECIES ', id_spec write(*,*) '#### CANNOT BE FOUND: CREATE FILE' write(*,*) '#### ',path(1)(1:length(1)),'SPECIES/SPECIES_',aspecnumb write(*,*) '#####################################################' stop 1000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "SPECIES_',aspecnumb,'.namelist' write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY #### ' write(*,'(a)') path(2)(1:length(2)) stop end subroutine readspecies