source: flexpart.git/src/par_mod.f90 @ 54cbd6c

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 54cbd6c was 842074e, checked in by Sabine <sabine.eckhardt@…>, 8 years ago

adapted parameter to run with 0.5 grid, updated SPECIES_031

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