source: trunk/src/par_mod.f90 @ 24

Last change on this file since 24 was 24, checked in by igpis, 10 years ago

version 9.2 beta. Changes from HH, AST, MC, NIK, IP. Changes in vert transform. New SPECIES input includes scavenging coefficients

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