source: branches/flexpart91_hasod/src_parallel/par_mod.f90 @ 8

Last change on this file since 8 was 8, checked in by hasod, 11 years ago

Added parallel version of Flexpart91

  • Property svn:executable set to *
File size: 11.4 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 10 August 2000                                            *
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
124  !integer,parameter :: nxmax=361,nymax=181,nuvzmax=26,nwzmax=26,nzmax=26
125  !integer,parameter :: nxmax=721,nymax=361,nuvzmax=64,nwzmax=64,nzmax=64
126  !integer,parameter :: nxmax=1201,nymax=235,nuvzmax=58,nwzmax=58,nzmax=58
127  integer,parameter :: nxshift=359 ! for ECMWF
128  !integer,parameter :: nxshift=0     ! for GFS
129
130  integer,parameter :: nconvlevmax = nuvzmax-1
131  integer,parameter :: na = nconvlevmax+1
132
133
134  ! nxmax,nymax        maximum dimension of wind fields in x and y
135  !                    direction, respectively
136  ! nuvzmax,nwzmax     maximum dimension of (u,v) and (w) wind fields in z
137  !                    direction (for fields on eta levels)
138  ! nzmax              maximum dimension of wind fields in z direction
139  !                    for the transformed Cartesian coordinates
140  ! nxshift            for global grids (in x), the grid can be shifted by
141  !                    nxshift grid points, in order to accomodate nested
142  !                    grids, and output grids overlapping the domain "boundary"
143  !                    nxshift must not be negative; "normal" setting would be 0
144  ! ntracermax         maximum number of tracer species in convection
145  ! nconvlevmax        maximum number of levels for convection
146  ! na                 parameter used in Emanuel's convect subroutine
147
148
149  !*********************************************
150  ! Maximum dimensions of the nested input grids
151  !*********************************************
152
153  integer,parameter :: maxnests=1, nxmaxn=0, nymaxn=0
154  !integer,parameter :: maxnests=1,nxmaxn=251,nymaxn=151
155
156  ! maxnests                maximum number of nested grids
157  ! nxmaxn,nymaxn           maximum dimension of nested wind fields in
158  !                         x and y direction, respectively
159
160
161  !*********************************
162  ! Parmaters for GRIB file decoding
163  !*********************************
164
165  integer,parameter :: jpack=4*nxmax*nymax, jpunp=4*jpack
166
167  ! jpack,jpunp             maximum dimensions needed for GRIB file decoding
168
169
170  !**************************************
171  ! Maximum dimensions of the output grid
172  !**************************************
173
174  !integer,parameter :: maxageclass=1,maxzgrid=10,nclassunc=1
175  integer,parameter :: maxageclass=1
176  integer,parameter :: nclassunc=1
177
178  ! nclassunc               number of classes used to calculate the uncertainty
179  !                         of the output
180  ! maxageclass             maximum number of age classes used for output
181
182  ! Sabine Eckhardt, June, 2008
183  ! the dimensions of the OUTGRID are now set dynamically during runtime
184  ! maxxgrid,maxygrid,maxzgrid    maximum dimensions in x,y,z direction
185  ! maxxgridn,maxygridn           maximum dimension of the nested grid
186  !integer maxxgrid,maxygrid,maxzgrid,maxxgridn,maxygridn
187  !integer,parameter :: maxxgrid=361,maxygrid=181,maxxgridn=0,maxygridn=0)
188
189  integer,parameter :: maxreceptor=20
190
191  ! maxreceptor             maximum number of receptor points
192
193
194  !**************************************************
195  ! Maximum number of particles, species, and similar
196  !**************************************************
197
198  integer,parameter :: maxpart=3500000
199  integer,parameter :: maxspec=1
200
201
202  ! maxpart                 Maximum number of particles
203  ! maxspec                 Maximum number of chemical species per release
204
205  ! maxpoint is also set dynamically during runtime
206  ! maxpoint                Maximum number of release locations
207
208  ! ---------
209  ! Sabine Eckhardt: change of landuse inventary numclass=13
210  ! ---------
211  integer,parameter :: maxwf=5000, maxtable=1000, numclass=13, ni=11
212
213  ! maxwf                   maximum number of wind fields to be used for simulation
214  ! maxtable                Maximum number of chemical species that can be
215  !                         tabulated for FLEXPART
216  ! numclass                Number of landuse classes available to FLEXPART
217  ! ni                      Number of diameter classes of particles
218
219  !**************************************************************************
220  ! dimension of the OH field
221  !**************************************************************************
222  integer,parameter :: maxxOH=72, maxyOH=46, maxzOH=7
223
224  !**************************************************************************
225  ! Maximum number of particles to be released in a single atmospheric column
226  ! for the domain-filling trajectories option
227  !**************************************************************************
228
229  integer,parameter :: maxcolumn=3000
230
231
232  !*********************************
233  ! Dimension of random number field
234  !*********************************
235
236  integer,parameter :: maxrand=2000000
237
238  ! maxrand                 number of random numbers used
239
240
241  !*****************************************************
242  ! Number of clusters to be used for plume trajectories
243  !*****************************************************
244
245  integer,parameter :: ncluster=5
246
247  !************************************
248  ! Unit numbers for input/output files
249  !************************************
250
251  integer,parameter :: unitpath=1, unitcommand=1, unitageclasses=1, unitgrid=1
252  integer,parameter :: unitavailab=1, unitreleases=88, unitpartout=93
253  integer,parameter :: unitpartin=93, unitflux=98, unitouttraj=96
254  integer,parameter :: unitvert=1, unitoro=1, unitpoin=1, unitreceptor=1
255  integer,parameter :: unitoutgrid=97, unitoutgridppt=99, unitoutinfo=1
256  integer,parameter :: unitspecies=1, unitoutrecept=91, unitoutreceptppt=92
257  integer,parameter :: unitlsm=1, unitsurfdata=1, unitland=1, unitwesely=1
258  integer,parameter :: unitOH=1
259  integer,parameter :: unitdates=94, unitheader=90, unitshortpart=95
260  integer,parameter :: unitboundcond=89
261
262end module par_mod
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG