source: flexpart.git/options/SPECIES/specoverview.f90 @ dba4221

bugfixes+enhancements
Last change on this file since dba4221 was dba4221, checked in by Pirmin Kaufmann <pirmin.kaufmann@…>, 18 months ago

Bugfixes:

  • options/SPECIES/SPECIES_009: corrected wrong number format, replaced comma by decimal point
  • options/SPECIES/SPECIES_028: corrected wrong number format, moved sign of exponent to after the E
  • options/SPECIES/specoverview.f90: added namelist parameters that appear in SPECIES files but were missing here
  • src/FLEXPART.f90: replaced compiler-specific command line argument routines by standard Fortran intrinsic routines
  • src/FLEXPART_MPI.f90: ditto
  • src/gridcheck_ecmwf.f90: corrected handling of vertical levels when input files do not contain uppermost layers
  • src/gridcheck_nests.f90: ditto
  • src/readwind_ecmwf.f90: corrected handling of vertical levels when input files do not contain uppermost layers
  • readwind_ecmwf_mpi.f90: ditto

Code enhancements:

  • options/OUTGRID: added comments describing contents
  • options/SPECIES/SPECIES_*: aligned comments
  • options/SPECIES/specoverview.f90: removed commented lines, rectified lines indenting
  • src/FLEXPART.f90: rectified lines indenting, updated date in version string
  • src/FLEXPART_MPI.f90: ditto, and realigned code with src/FLEXPART.f90
  • src/gridcheck_*.f90: added code to write out name of file before it is opened (helps a lot when an input file causes troubles)
  • src/par_mod.f90: added comment explaining relevance of nuvzmax for GRIB input
  • src/readreleases.f90: write out warning if too few particles are used to randomize release
  • src/readspecies.f90: write out name of SPECIES file before it is read
  • src/readwind_*.f90: write out name of input file before opening it
  • src/writeheader_txt.f90: removed wrong comment
  • Property mode set to 100644
File size: 4.5 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!**********************************************************************
21program specoverview
22  implicit none
23
24  character(len=11) :: speciesfn
25  character(len=3)  :: aspec
26  character(len=16) :: pspecies
27  real :: pdecay, pweta_gas, pwetb_gas, preldiff, phenry, pf0, pdensity, pdquer
28  real :: pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst
29  real :: pcrain_aero, pcsnow_aero, pccn_aero, pin_aero
30  real :: parea_dow(7), parea_hour(24), ppoint_dow(7), ppoint_hour(24)
31  integer :: ierr, unitspecies, specnumber
32
33  ! declare namelist
34  namelist /species_params/ &
35       pspecies, pdecay, pweta_gas, pwetb_gas, &
36       pcrain_aero, pcsnow_aero, pccn_aero, pin_aero, &
37       preldiff, phenry, pf0, pdensity, pdquer, &
38       pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, &
39       parea_dow, parea_hour, ppoint_dow, ppoint_hour
40
41  unitspecies=4
42
43  write(*,*) '    Species   |       |   WetDep(gas)   |    DryDep(gas)   |WetDep(below-C)| WetDep(in-C)|'// &
44       '     DryDepo(particles)  Altern| Radioact.  |     OH Reaction      |'
45
46  write(*,*) '    Name      |molwght| A          B    | D    H        f0 | Crain   Csnow |  ccn    in  |'// &
47       '   rho    dquer    dsig    vd  | Halflife[s]|   C**     D[T]  N*** |'
48
49  write(*,*) '--------------|-------|-----------------|------------------|---------------|-------------|'// &
50       '-------------------------------|------------|----------------------|'
51
52
53  do specnumber=1,100
54
55     write (aspec,'(i0.3)') specnumber
56     speciesfn='SPECIES_'//aspec
57
58     ! write(*,*) 'Processing: ',speciesfn
59
60     pspecies="" ! read failure indicator value
61     pdecay=-9.9
62     pweta_gas=-0.9E-09
63     pwetb_gas=0.0
64     pcrain_aero=-9.9
65     pcsnow_aero=-9.9
66     pccn_aero=-9.9
67     pin_aero=-9.9
68     preldiff=-9.9
69     phenry=0.0
70     pf0=0.0
71     pdensity=-0.9E09
72     pdquer=0.0
73     pdsigma=0.0
74     pdryvel=-9.99
75     pohcconst=-9.9
76     pohdconst=-9.9
77     pohnconst=2.0
78     pweightmolar=-9.9
79
80     ! Open the SPECIES file and read species names and properties
81     !************************************************************
82     open(unitspecies,file=speciesfn,status='old',form='formatted',iostat=ierr)
83     if (ierr /= 0) then
84        ! Report missing files below 40
85        if (specnumber <= 40) then
86           write(*,'(i3,2(1x,a))') specnumber, 'no such file:', trim(speciesfn)
87        end if
88        cycle
89     end if
90     read(unitspecies,species_params)  ! to skip errors add: ,err=998
91     close(unitspecies)
92
93     write(*,45) specnumber,' ',pspecies,'|',pweightmolar,'|',pweta_gas,' ',pwetb_gas,'|', &
94          preldiff,' ',phenry,' ',pf0,'|', &
95          pcrain_aero,' ',pcsnow_aero,'|',pccn_aero,' ',pin_aero,'|', &
96          pdensity,pdquer,pdsigma,pdryvel,'|',pdecay,'|',pohcconst,pohdconst,pohnconst,'|'
97
9845   format(i3,a1,a11,a1,f7.1,a1,e8.1,a1,f8.2,a1, &
99          f4.1,a1,e8.1,a1,f4.1,a1, &
100          f7.1,a1,f7.1,a1,f6.1,a1,f6.1,a1, &
101          e8.1,e9.1,f7.1,f7.2,a1,f12.1,a1,e8.1,f7.1,f7.1,a1)
102
103998  continue
104  enddo
105
106  write(*,*) '** unit [cm^3/molec/s] (in FLEXPART version 9.2 and below this had unit [cm3/s], note the unit is now changed!)'
107  write(*,*) '*** no unit'
108
109  print*,'rho: density'
110
111end program specoverview
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG