source: flexpart.git/src/par_mod.f90 @ adf46ae

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since adf46ae was adf46ae, checked in by Espen Sollum ATMOS <eso@…>, 9 years ago

Added module gfs_mod / ecmwf_mod to allow compilation of different versions without editing source code

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