source: flexpart.git/src/par_mod.f90 @ 25b4532

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

turbulence factors can change for different runs with the same executable

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