source: flexpart.git/src/par_mod.f90

bugfixes+enhancements
Last change on this file 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: 12.4 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4!*******************************************************************************
5!   Include file for calculation of particle trajectories (Program FLEXPART)   *
6!        This file contains the parameter statements used in FLEXPART          *
7!                                                                              *
8!        Author: A. Stohl                                                      *
9!                                                                              *
10!        1997                                                                  *
11!                                                                              *
12!        Update 15 August 2013 IP                                              *
13!                                                                              *
14!                                                                              *
15!*******************************************************************************
16
17module par_mod
18
19  implicit none
20
21  !****************************************************************
22  ! Parameters defining KIND parameter for double/single precision
23  !****************************************************************
24
25  integer,parameter :: dp=selected_real_kind(P=15)
26  integer,parameter :: sp=selected_real_kind(6)
27
28  !****************************************************************
29  ! dep_prec sets the precision for deposition calculations (sp or
30  ! dp). sp is default, dp can be used for increased precision.
31  !****************************************************************
32
33  integer,parameter :: dep_prec=sp
34
35  !****************************************************************
36  ! Set to F to disable use of kernel for concentrations/deposition
37  !****************************************************************
38
39  logical, parameter :: lusekerneloutput=.true.
40
41  !*********************************************************************
42  ! Set to T to change output units to number of particles per grid cell
43  !*********************************************************************
44  logical, parameter :: lparticlecountoutput=.false.
45
46  !***********************************************************
47  ! number of directories/files used for FLEXPART input/output
48  !***********************************************************
49
50  integer,parameter :: numpath=4
51
52  ! numpath                 Number of different pathnames for input/output files
53
54
55  !*****************************
56  ! Physical and other constants
57  !*****************************
58
59  real,parameter :: pi=3.14159265, r_earth=6.371e6, r_air=287.05, ga=9.81
60  real,parameter :: cpa=1004.6, kappa=0.286, pi180=pi/180., vonkarman=0.4
61  ! additional constants RLT Aug-2017
62  real,parameter :: rgas=8.31447
63  real,parameter :: r_water=461.495
64
65  ! pi                      number "pi"
66  ! pi180                   pi/180.
67  ! r_earth                 radius of earth [m]
68  ! r_air                   individual gas constant for dry air [J/kg/K]
69  ! ga                      gravity acceleration of earth [m/s**2]
70  ! cpa                     specific heat for dry air
71  ! kappa                   exponent of formula for potential temperature
72  ! vonkarman               von Karman constant
73  ! rgas                    universal gas constant [J/mol/K]
74  ! r_water                 specific gas constant for water vapor [J/kg/K]
75
76  real,parameter :: karman=0.40, href=15., convke=2.0
77  real,parameter :: hmixmin=100., hmixmax=4500. !, turbmesoscale=0.16
78  !real,parameter :: d_trop=50., d_strat=0.1
79  real :: d_trop=50., d_strat=0.1, turbmesoscale=0.16 ! turbulence factors can change for different runs
80  real,parameter :: rho_water=1000. !ZHG 2015 [kg/m3]
81  !ZHG MAR2016
82  real,parameter :: incloud_ratio=6.2
83
84  ! karman                  Karman's constant
85  ! href [m]                Reference height for dry deposition
86  ! konvke                  Relative share of kinetic energy used for parcel lifting
87  ! hmixmin,hmixmax         Minimum and maximum allowed PBL height
88  ! turbmesoscale           the factor by which standard deviations of winds at grid
89  !                    points surrounding the particle positions are scaled to
90  !                    yield the scales for the mesoscale wind velocity fluctuations
91  ! d_trop [m2/s]           Turbulent diffusivity for horizontal components in the troposphere
92  ! d_strat [m2/s]          Turbulent diffusivity for vertical component in the stratosphere
93
94  real,parameter :: xmwml=18.016/28.960
95
96  ! xmwml   ratio of molar weights of water vapor and dry air
97  !****************************************************
98  ! Constants related to the stratospheric ozone tracer
99  !****************************************************
100
101  real,parameter :: ozonescale=60., pvcrit=2.0
102
103  ! ozonescale              ppbv O3 per PV unit
104  ! pvcrit                  PV level of the tropopause
105
106
107
108  !********************
109  ! Some time constants
110  !********************
111
112  integer,parameter :: idiffnorm=10800, idiffmax=2*idiffnorm, minstep=1
113
114  ! idiffnorm [s]           normal time interval between two wind fields
115  ! idiffmax [s]            maximum time interval between two wind fields
116  ! minstep [s]             minimum time step to be used within FLEXPART
117
118
119  !*****************************************************************
120  ! Parameters for polar stereographic projection close to the poles
121  !*****************************************************************
122
123  real,parameter :: switchnorth=75., switchsouth=-75.
124
125  ! switchnorth    use polar stereographic grid north of switchnorth
126  ! switchsouth    use polar stereographic grid south of switchsouth
127
128
129  !*********************************************
130  ! Maximum dimensions of the input mother grids
131  !*********************************************
132 
133  ! NOTE: dimensioning of zsec2 in gridcheck depends on nuvzmax, therefore nuvzmax
134  ! must represent all levels even if only lower levels are in the input files.
135
136  ! ECMWF
137! integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92,nxshift=359 ! 1.0 degree 92 level
138!  integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=0 ! 1.0 degree 138 level
139!   integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=359 ! 1.0 degree 138 level
140! integer,parameter :: nxmax=721,nymax=361,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=359  ! 0.5 degree 138 level
141!  integer,parameter :: nxmax=181,nymax=91,nuvzmax=92,nwzmax=92,nzmax=92,nxshift=0  ! CERA 2.0 degree 92 level
142
143! GFS
144   integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138
145   integer :: nxshift=0 ! shift not fixed for the executable
146
147
148  !*********************************************
149  ! Maximum dimensions of the nested input grids
150  !*********************************************
151
152  integer,parameter :: maxnests=0,nxmaxn=0,nymaxn=0
153
154  ! nxmax,nymax        maximum dimension of wind fields in x and y
155  !                    direction, respectively
156  ! nuvzmax,nwzmax     maximum dimension of (u,v) and (w) wind fields in z
157  !                    direction (for fields on eta levels)
158  ! nzmax              maximum dimension of wind fields in z direction
159  !                    for the transformed Cartesian coordinates
160  ! nxshift            for global grids (in x), the grid can be shifted by
161  !                    nxshift grid points, in order to accomodate nested
162  !                    grids, and output grids overlapping the domain "boundary"
163  !                    nxshift must not be negative; "normal" setting would be 0
164
165 
166  integer,parameter :: nconvlevmax = nuvzmax-1
167  integer,parameter :: na = nconvlevmax+1
168
169  ! ntracermax         maximum number of tracer species in convection
170  ! nconvlevmax        maximum number of levels for convection
171  ! na                 parameter used in Emanuel's convect subroutine
172
173
174  !*********************************
175  ! Parmaters for GRIB file decoding
176  !*********************************
177
178  integer,parameter :: jpack=4*nxmax*nymax, jpunp=4*jpack
179
180  ! jpack,jpunp             maximum dimensions needed for GRIB file decoding
181
182
183  !**************************************
184  ! Maximum dimensions of the output grid
185  !**************************************
186
187  !integer,parameter :: maxageclass=1,maxzgrid=10,nclassunc=1
188  integer,parameter :: maxageclass=1,nclassunc=1
189
190  ! nclassunc               number of classes used to calculate the uncertainty
191  !                         of the output
192  ! maxageclass             maximum number of age classes used for output
193
194  ! Sabine Eckhardt, June, 2008
195  ! the dimensions of the OUTGRID are now set dynamically during runtime
196  ! maxxgrid,maxygrid,maxzgrid    maximum dimensions in x,y,z direction
197  ! maxxgridn,maxygridn           maximum dimension of the nested grid
198  !integer maxxgrid,maxygrid,maxzgrid,maxxgridn,maxygridn
199  !integer,parameter :: maxxgrid=361,maxygrid=181,maxxgridn=0,maxygridn=0)
200
201  integer,parameter :: maxreceptor=20
202
203  ! maxreceptor             maximum number of receptor points
204
205
206  !**************************************************
207  ! Maximum number of particles, species, and similar
208  !**************************************************
209
210  integer,parameter :: maxpart=100000
211  integer,parameter :: maxspec=1
212
213  real,parameter :: minmass=0.0001
214
215  ! maxpart                 Maximum number of particles
216  ! maxspec                 Maximum number of chemical species per release
217  ! minmass                 Terminate particles carrying less mass
218
219  ! maxpoint is also set dynamically during runtime
220  ! maxpoint                Maximum number of release locations
221
222  ! ---------
223  ! Sabine Eckhardt: change of landuse inventary numclass=13
224  ! ---------
225  integer,parameter :: maxwf=50000, maxtable=1000, numclass=13, ni=11
226  integer,parameter :: numwfmem=2 ! Serial version/MPI with 2 fields
227  !integer,parameter :: numwfmem=3 ! MPI with 3 fields
228
229  ! maxwf                   maximum number of wind fields to be used for simulation
230  ! maxtable                Maximum number of chemical species that can be
231  !                         tabulated for FLEXPART
232  ! numclass                Number of landuse classes available to FLEXPART
233  ! ni                      Number of diameter classes of particles
234  ! numwfmem                Number of windfields kept in memory. 2 for serial
235  !                         version, 2 or 3 for MPI version
236
237  !**************************************************************************
238  ! dimension of the OH field
239  !**************************************************************************
240  integer,parameter :: maxxOH=72, maxyOH=46, maxzOH=7
241
242  !**************************************************************************
243  ! Maximum number of particles to be released in a single atmospheric column
244  ! for the domain-filling trajectories option
245  !**************************************************************************
246
247  integer,parameter :: maxcolumn=3000
248
249
250  !*********************************
251  ! Dimension of random number field
252  !*********************************
253
254  integer,parameter :: maxrand=1000000
255
256  ! maxrand                 number of random numbers used
257 
258
259  !*****************************************************
260  ! Number of clusters to be used for plume trajectories
261  !*****************************************************
262
263  integer,parameter :: ncluster=5
264
265  !************************************
266  ! Unit numbers for input/output files
267  !************************************
268
269  integer,parameter :: unitpath=1, unitcommand=1, unitageclasses=1, unitgrid=1
270  integer,parameter :: unitavailab=1, unitreleases=88, unitpartout=93, unitpartout_average=105
271  integer,parameter :: unitpartin=93, unitflux=98, unitouttraj=96
272  integer,parameter :: unitvert=1, unitoro=1, unitpoin=1, unitreceptor=1
273  integer,parameter :: unitoutgrid=97, unitoutgridppt=99, unitoutinfo=1
274  integer,parameter :: unitspecies=1, unitoutrecept=91, unitoutreceptppt=92
275  integer,parameter :: unitlsm=1, unitsurfdata=1, unitland=1, unitwesely=1
276  integer,parameter :: unitOH=1
277  integer,parameter :: unitdates=94, unitheader=90,unitheader_txt=100, unitshortpart=95, unitprecip=101
278  integer,parameter :: unitboundcond=89
279  integer,parameter :: unittmp=101
280! RLT
281  integer,parameter :: unitoutfactor=102
282
283!******************************************************
284! integer code for missing values, used in wet scavenging (PS, 2012)
285!******************************************************
286
287  integer,parameter ::  icmv=-9999
288
289
290end module par_mod
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG