source: branches/jerome/src_flexwrf_v3.1/par_mod.f90 @ 16

Last change on this file since 16 was 16, checked in by jebri, 10 years ago

sources for flexwrf v3.1

File size: 13.1 KB
Line 
1!***********************************************************************
2!* Copyright 2012,2013                                                *
3!* Jerome Brioude, Delia Arnold, Andreas Stohl, Wayne Angevine,       *
4!* John Burkhart, Massimo Cassiani, Adam Dingwell, Richard C Easter, Sabine Eckhardt,*
5!* Stephanie Evan, Jerome D Fast, Don Morton, Ignacio Pisso,          *
6!* Petra Seibert, Gerard Wotawa, Caroline Forster, Harald Sodemann,   *
7!                                                                     *
8!* This file is part of FLEXPART WRF                                   *
9!                                                                     *
10! FLEXPART is free software: you can redistribute it and/or modify    *
11! it under the terms of the GNU General Public License as published by*
12! the Free Software Foundation, either version 3 of the License, or   *
13! (at your option) any later version.                                 *
14!                                                                     *
15! FLEXPART is distributed in the hope that it will be useful,         *
16! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
17! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
18! GNU General Public License for more details.                        *
19!                                                                     *
20! You should have received a copy of the GNU General Public License   *
21! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
22!**********************************************************************
23
24!*******************************************************************************
25!   Include file for calculation of particle trajectories (Program FLEXPART)   *
26!        This file contains the parameter statements used in FLEXPART          *
27!                                                                              *
28!        Author: A. Stohl                                                      *
29!                                                                              *
30!        1997                                                                  *
31!                                                                              *
32!        Last update 10 August 2000                                            *
33!                                                                              *
34!*******************************************************************************
35
36module par_mod
37
38  implicit none
39
40  !****************************************************************
41  ! Parameter defining KIND parameter for "double precision"
42  !****************************************************************
43
44  integer,parameter :: dp=selected_real_kind(P=15)
45
46
47  !***********************************************************
48  ! Number of directories/files used for FLEXPART input/output
49  !***********************************************************
50
51  integer,parameter :: numpath=3
52
53  ! numpath                 Number of different pathnames for input/output files
54
55
56  !*****************************
57  ! Physical and other constants
58  !*****************************
59
60  real,parameter :: pi=3.14159265, r_earth=6.371e6, r_air=287.05,ga=9.81,weightair=28.97
61  real,parameter :: cpa=1004.6, kappa=0.286, pi180=pi/180., vonkarman=0.4
62  logical        :: strswitch
63  ! pi                      number "pi"
64  ! pi180                   pi/180.
65  ! r_earth                 radius of earth [m]
66  ! r_air                   individual gas constant for dry air [J/kg/K]
67  ! ga                      gravity acceleration of earth [m/s**2]
68  ! cpa                     specific heat for dry air
69  ! kappa                   exponent of formula for potential temperature
70  ! vonkarman               von Karman constant
71
72  real,parameter :: karman=0.40, href=15., convke=2.0
73  real,parameter :: hmixmin=100., hmixmax=4500., turbmesoscale=0.16
74  real,parameter :: d_trop=50., d_strat=0.1
75
76  ! karman                  Karman's constant
77  ! href [m]                Reference height for dry deposition
78  ! konvke                  Relative share of kinetic energy used for parcel lifting
79  ! hmixmin,hmixmax         Minimum and maximum allowed PBL height
80  ! turbmesoscale           the factor by which standard deviations of winds at grid
81  !                    points surrounding the particle positions are scaled to
82  !                    yield the scales for the mesoscale wind velocity fluctuations
83  ! d_trop [m2/s]           Turbulent diffusivity for horizontal components in the troposphere
84  ! d_strat [m2/s]          Turbulent diffusivity for vertical component in the stratosphere
85
86  real,parameter :: xmwml=18.016/28.960
87
88  ! xmwml   ratio of molar weights of water vapor and dry air
89  !****************************************************
90  ! Constants related to the stratospheric ozone tracer
91  !****************************************************
92
93  real,parameter :: ozonescale=60., pvcrit=2.0
94
95  ! ozonescale              ppbv O3 per PV unit
96  ! pvcrit                  PV level of the tropopause
97
98
99
100  !********************
101  ! Some time constants
102  !********************
103
104  integer,parameter :: idiffnorm=10800, idiffmax=2*idiffnorm, minstep=1
105
106  ! idiffnorm [s]           normal time interval between two wind fields
107  ! idiffmax [s]            maximum time interval between two wind fields
108  ! minstep [s]             minimum time step to be used within FLEXPART
109
110
111  !*****************************************************************
112  ! Parameters for polar stereographic projection close to the poles
113  !*****************************************************************
114
115  real,parameter :: switchnorth=75., switchsouth=-75.
116
117  ! switchnorth    use polar stereographic grid north of switchnorth
118  ! switchsouth    use polar stereographic grid south of switchsouth
119
120
121  !*********************************************
122  ! Maximum dimensions of the input mother grids
123  !*********************************************
124
125  !integer,parameter :: nxmax=364,nymax=244,nuvzmax=45,nwzmax=45,nzmax=45
126  !integer,parameter :: nxmax=454,nymax=334,nuvzmax=45,nwzmax=45,nzmax=45
127  integer,parameter :: nxmax=334,nymax=334,nuvzmax=61,nwzmax=61,nzmax=61
128  !integer,parameter :: nxmax=182,nymax=182,nuvzmax=61,nwzmax=61,nzmax=61
129  !integer,parameter :: nxmax=1081,nymax=260,nuvzmax=89,nwzmax=89,nzmax=89
130
131  !integer,parameter :: nxmax=45,nymax=33,nuvzmax=45,nwzmax=45,nzmax=45
132  !integer,parameter :: nxmax=361,nymax=181,nuvzmax=61,nwzmax=61,nzmax=61
133  !integer,parameter :: nxmax=721,nymax=361,nuvzmax=64,nwzmax=64,nzmax=64
134  !integer,parameter :: nxshift=359  ! for ECMWF
135  integer,parameter :: nxshift=0     ! for GFS
136
137  integer,parameter :: nconvlevmax = nuvzmax-1
138  integer,parameter :: na = nconvlevmax+1
139
140
141  ! nxmax,nymax        maximum dimension of wind fields in x and y
142  !                    direction, respectively
143  ! nuvzmax,nwzmax     maximum dimension of (u,v) and (w) wind fields in z
144  !                    direction (for fields on eta levels)
145  ! nzmax              maximum dimension of wind fields in z direction
146  !                    for the transformed Cartesian coordinates
147  ! nxshift            for global grids (in x), the grid can be shifted by
148  !                    nxshift grid points, in order to accomodate nested
149  !                    grids, and output grids overlapping the domain "boundary"
150  !                    nxshift must not be negative; "normal" setting would be 0
151  ! ntracermax         maximum number of tracer species in convection
152  ! nconvlevmax        maximum number of levels for convection
153  ! na                 parameter used in Emanuel's convect subroutine
154
155
156  !*********************************************
157  ! Maximum dimensions of the nested input grids
158  !*********************************************
159
160  !integer,parameter :: maxnests=0, nxmaxn=0, nymaxn=0
161   integer,parameter :: maxnests=1,nxmaxn=312,nymaxn=312
162  !integer,parameter :: maxnests=1,nxmaxn=312,nymaxn=312
163
164  ! maxnests                maximum number of nested grids
165  ! nxmaxn,nymaxn           maximum dimension of nested wind fields in
166  !                         x and y direction, respectively
167
168
169  !*********************************
170  ! Parmaters for GRIB file decoding
171  !*********************************
172
173  integer,parameter :: jpack=4*nxmax*nymax, jpunp=4*jpack
174
175  ! jpack,jpunp             maximum dimensions needed for GRIB file decoding
176
177
178  !**************************************
179  ! Maximum dimensions of the output grid
180  !**************************************
181
182  !integer,parameter :: maxageclass=1,maxzgrid=10,nclassunc=1
183  integer,parameter :: maxageclass=3,nclassunc=1
184
185  ! nclassunc               number of classes used to calculate the uncertainty
186  !                         of the output
187  ! maxageclass             maximum number of age classes used for output
188
189  ! Sabine Eckhardt, June, 2008
190  ! the dimensions of the OUTGRID are now set dynamically during runtime
191  ! maxxgrid,maxygrid,maxzgrid    maximum dimensions in x,y,z direction
192  ! maxxgridn,maxygridn           maximum dimension of the nested grid
193  !integer maxxgrid,maxygrid,maxzgrid,maxxgridn,maxygridn
194  !integer,parameter :: maxxgrid=361,maxygrid=181,maxxgridn=0,maxygridn=0)
195
196  integer,parameter :: maxreceptor=200
197
198  ! maxreceptor             maximum number of receptor points
199
200
201   integer,parameter :: turb_option_none=0
202   integer,parameter :: turb_option_diagnosed=1
203   integer,parameter :: turb_option_tke=2
204   integer,parameter :: turb_option_mytke=3
205   integer,parameter :: sfc_option_diagnosed=0
206   integer,parameter :: sfc_option_wrf=1
207   integer,parameter :: partoutput_use_nested=1
208  !**************************************************
209  ! Maximum number of particles, species, and similar
210  !**************************************************
211
212  integer :: maxpart=1
213  integer,parameter :: maxspec=11
214
215
216  ! maxpart                 Maximum number of particles
217  ! maxspec                 Maximum number of chemical species per release
218
219  ! maxpoint is also set dynamically during runtime
220  ! maxpoint                Maximum number of release locations
221
222  ! ---------
223  ! Sabine Eckhardt: change of landuse inventary numclass=13
224  ! ---------
225  integer,parameter :: maxwf=50000, maxtable=1000, numclass=13, ni=11
226
227  ! maxwf                   maximum number of wind fields to be used for simulation
228  ! maxtable                Maximum number of chemical species that can be
229  !                         tabulated for FLEXPART
230  ! numclass                Number of landuse classes available to FLEXPART
231  ! ni                      Number of diameter classes of particles
232
233  !**************************************************************************
234  ! dimension of the OH field
235  !**************************************************************************
236  integer,parameter :: maxxOH=72, maxyOH=46, maxzOH=7
237
238  !**************************************************************************
239  ! Maximum number of particles to be released in a single atmospheric column
240  ! for the domain-filling trajectories option
241  !**************************************************************************
242
243  integer,parameter :: maxcolumn=3000
244
245
246  !*********************************
247  ! Dimension of random number field
248  !*********************************
249
250  integer,parameter :: newrandomgen = 0  !added by mc to select teh new parallel random generator ; 0 is the old one if zero is chosen then adjust teh definition of rannumb and uniform_rannumb in com_mod.f90
251! integer :: newrandomgen = 0  ! JB version
252
253  integer,parameter :: maxrand=5000000 !comment by mc: maximum number of gasussina distributed and random distributed random number for a single mpi_process
254  ! maxrand                 number of random numbers used
255  integer, parameter :: MAX_STREAM = 12 !added by mc : maximum total number of stream initilized (i.e. avilable) for the MT generator.
256
257  integer,parameter :: maxomp=12
258  integer,parameter :: maxrandomp=maxrand*maxomp
259  integer,parameter :: maxrand3=maxrand*(newrandomgen+maxomp*(1-newrandomgen))
260
261  !*****************************************************
262  ! Number of clusters to be used for plume trajectories
263  !*****************************************************
264
265  integer,parameter :: ncluster=5
266
267  !************************************
268  ! Unit numbers for input/output files
269  !************************************
270
271  integer,parameter :: unitpath=1, unitcommand=1, unitageclasses=1, unitgrid=1
272  integer,parameter :: unitavailab=3, unitreleases=1, unitpartout=93
273  integer,parameter :: unitpartin=93, unitflux=98, unitouttraj=96
274  integer,parameter :: unitvert=1, unitoro=1, unitpoin=1, unitreceptor=1
275  integer,parameter :: unitoutgrid=97, unitoutgridppt=99, unitoutinfo=1
276  integer,parameter :: unitspecies=1, unitoutrecept=91, unitoutreceptppt=92
277  integer,parameter :: unitlsm=1, unitsurfdata=1, unitland=1, unitwesely=1
278  integer,parameter :: unitOH=1
279  integer,parameter :: unitdates=94, unitheader=90, unitshortpart=95
280  integer,parameter :: unitboundcond=89
281
282  ! CDA implementing a quick fix for the wet deposition scheme
283  !******************************************************
284  ! integer code for missing values, used in wet scavenging (PS, 2012)
285  !******************************************************
286
287      integer icmv
288      parameter(icmv=-9999)
289
290end module par_mod
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG