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

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

Code for cloud water should be correct if the total cw is stored in field clwc (old scheme) or in field qc (new scheme). Minor edits in some files.

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