source: flexpart.git/options.reference/SPECIES/specoverview.f90 @ 0ff3b23

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 0ff3b23 was 0ff3b23, checked in by Ignacio Pisso <ip@…>, 5 years ago

add options.reference/ containing previous versions of user input files

  • Property mode set to 100644
File size: 5.0 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  implicit none
22
23  character(len=11) :: speciesfn
24  character(len=3)  :: aspec
25  character(len=16) :: pspecies
26  real :: pdecay, pweta_gas, pwetb_gas, preldiff, phenry, pf0, pdensity, pdquer
27  real :: pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst
28  real :: pcrain_aero, pcsnow_aero, pccn_aero, pin_aero
29  integer :: readerror, unitspecies, specnumber
30
31! declare namelist
32  namelist /species_params/ &
33       pspecies, pdecay, pweta_gas, pwetb_gas, &
34       pcrain_aero, pcsnow_aero, pccn_aero, pin_aero, &
35       preldiff, phenry, pf0, pdensity, pdquer, &
36       pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst
37
38  unitspecies=4
39
40  write(*,*) '    Species   |       |   WetDep(gas)   |    DryDep(gas)   |WetDep(below-C)| WetDep(in-C)|'//&
41             '     DryDepo(particles)  Altern| Radioact.  |     OH Reaction      |'
42
43  write(*,*) '    Name      |molwght| A          B    | D    H        f0 | Crain   Csnow |  ccn    in  |' //&
44             '   rho    dquer    dsig    vd  | Halflife[s]|   C**     D[T]  N*** |'
45
46  write(*,*) '--------------|-------|-----------------|------------------|---------------|-------------|'//&
47             '-------------------------------|------------|----------------------|'
48
49
50! write(*,*) '    Specie    | Radioact.  | WetDep(gas)     |WetDep(below-C)| WetDep(in-C)|     DryDepo(gas)  |'//&
51!            '     DryDepo(particles)  Altern|       |     OH Reaction      |'
52! write(*,*) '    Name      | Halflife[s]|  A         B    |  Crain  Csnow | ccn    in   |   D      H    f0  |' //&
53!            '   rho    dquer    dsig    vd  |molwght|   C**     D[T]  N*** |'
54! write(*,*) '--------------|------------|-----------------|---------------|-------------|-------------------|'//&
55!            '-------------------------------|-------|----------------------|'
56
57  do specnumber=1,100
58 
59  write (aspec,'(i0.3)') specnumber
60  speciesfn='SPECIES_'//aspec
61 
62! write(*,*) 'Processing: ',speciesfn
63
64  pspecies="" ! read failure indicator value
65  pdecay=-9.9
66  pweta_gas=-0.9E-09
67  pwetb_gas=0.0
68  pcrain_aero=-9.9
69  pcsnow_aero=-9.9
70  pccn_aero=-9.9
71  pin_aero=-9.9
72  preldiff=-9.9
73  phenry=0.0
74  pf0=0.0
75  pdensity=-0.9E09
76  pdquer=0.0
77  pdsigma=0.0
78  pdryvel=-9.99
79  pohcconst=-9.9
80  pohdconst=-9.9
81  pohnconst=2.0
82  pweightmolar=-9.9
83
84! Open the SPECIES file and read species names and properties
85!************************************************************
86  open(unitspecies,file=speciesfn,status='old',form='formatted',err=998)
87  read(unitspecies,species_params,err=998)
88  close(unitspecies)
89 
90  write(*,45) specnumber,' ',pspecies,'|',pweightmolar,'|',pweta_gas,' ',pwetb_gas,'|', &
91              preldiff,' ',phenry,' ',pf0,'|', &
92              pcrain_aero,' ',pcsnow_aero,'|',pccn_aero,' ',pin_aero,'|', &
93              pdensity,pdquer,pdsigma,pdryvel,'|',pdecay,'|',pohcconst,pohdconst,pohnconst,'|'
94
9545 format(i3,a1,a11,a1,f7.1,a1,e8.1,a1,f8.2,a1, &
96          f4.1,a1,e8.1,a1,f4.1,a1, &
97          f7.1,a1,f7.1,a1,f6.1,a1,f6.1,a1, &
98          e8.1,e9.1,f7.1,f7.2,a1,f12.1,a1,e8.1,f7.1,f7.1,a1)
99
100!  write(*,45) specnumber,' ',pspecies,'|',pdecay,'|',pweta_gas,' ',pwetb_gas,'|',pcrain_aero,' ', &
101!            pcsnow_aero,'|',pccn_aero,' ',pin_aero,'|',preldiff,' ',phenry,' ',pf0,'|', &
102!             pdensity,pdquer,pdsigma,pdryvel,'|',pweightmolar,'|',pohcconst,pohdconst,pohnconst,'|'
103
104!5 format(i3,a1,a11,a1,f12.1,a1,e8.1,a1,f8.2,a1,f7.1,a1,f7.1,a1,f6.1,a1,f6.1,a1,f5.1,a1,e8.1,a1,f4.1,a1, &
105!         e8.1,e9.1,f7.1,f7.2,a1,f7.1,a1,e8.1,f7.1,f7.1,a1)
106           
107998 continue
108enddo
109
110write(*,*) '** unit [cm^3/molec/s] (in FLEXPART version 9.2 and below this had unit [cm3/s], note the unit is now changed!)'
111write(*,*) '*** no unit'
112
113
114end
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG