1 | !******************************************************************************* |
---|
2 | ! Include file for particle diffusion model FLEXPART * |
---|
3 | ! This file contains a global common block used by FLEXPART * |
---|
4 | ! * |
---|
5 | ! Author: A. Stohl * |
---|
6 | ! * |
---|
7 | ! June 1996 * |
---|
8 | ! * |
---|
9 | ! Last update:15 August 2013 IP * |
---|
10 | ! * |
---|
11 | !******************************************************************************* |
---|
12 | |
---|
13 | module com_mod |
---|
14 | |
---|
15 | use par_mod, only: dp, numpath, maxnests, maxageclass, maxspec, ni, & |
---|
16 | numclass, nymax, nxmax, maxcolumn, maxwf, nzmax, nxmaxn, nymaxn, & |
---|
17 | maxreceptor, maxpart, maxrand, nwzmax, nuvzmax |
---|
18 | |
---|
19 | implicit none |
---|
20 | |
---|
21 | !**************************************************************** |
---|
22 | ! Variables defining where FLEXPART input/output files are stored |
---|
23 | !**************************************************************** |
---|
24 | |
---|
25 | character :: path(numpath+2*maxnests)*120 |
---|
26 | integer :: length(numpath+2*maxnests) |
---|
27 | character(len=256) :: pathfile, flexversion, arg1, arg2 |
---|
28 | |
---|
29 | ! path path names needed for trajectory model |
---|
30 | ! length length of path names needed for trajectory model |
---|
31 | ! pathfile file where pathnames are stored |
---|
32 | ! flexversion version of flexpart |
---|
33 | ! arg input arguments from launch at command line |
---|
34 | |
---|
35 | !******************************************************** |
---|
36 | ! Variables defining the general model run specifications |
---|
37 | !******************************************************** |
---|
38 | |
---|
39 | integer :: ibdate,ibtime,iedate,ietime |
---|
40 | real(kind=dp) :: bdate,edate |
---|
41 | |
---|
42 | |
---|
43 | ! ibdate beginning date (YYYYMMDD) |
---|
44 | ! ibtime beginning time (HHMISS) |
---|
45 | ! iedate ending date (YYYYMMDD) |
---|
46 | ! ietime ending time (HHMISS) |
---|
47 | ! bdate beginning date of simulation (julian date) |
---|
48 | ! edate ending date of simulation (julian date) |
---|
49 | |
---|
50 | |
---|
51 | integer :: ldirect,ideltas |
---|
52 | |
---|
53 | ! ldirect 1 for forward, -1 for backward simulation |
---|
54 | ! ideltas length of trajectory loop from beginning to |
---|
55 | ! ending date (s) |
---|
56 | |
---|
57 | integer :: loutstep,loutaver,loutsample,method,lsynctime |
---|
58 | real :: outstep |
---|
59 | |
---|
60 | ! loutstep [s] gridded concentration output every loutstep seconds |
---|
61 | ! loutaver [s] concentration output is an average over [s] seconds |
---|
62 | ! loutsample [s] sampling interval of gridded concentration output |
---|
63 | ! lsynctime [s] synchronisation time of all particles |
---|
64 | ! method indicator which dispersion method is to be used |
---|
65 | ! outstep = real(abs(loutstep)) |
---|
66 | |
---|
67 | real :: ctl,fine |
---|
68 | integer :: ifine,iout,ipout,ipin,iflux,mdomainfill |
---|
69 | integer :: mquasilag,nested_output,ind_source,ind_receptor |
---|
70 | integer :: ind_rel,ind_samp,ioutputforeachrelease,linit_cond,surf_only |
---|
71 | logical :: turbswitch |
---|
72 | |
---|
73 | ! ctl factor, by which time step must be smaller than Lagrangian time scale |
---|
74 | ! ifine reduction factor for time step used for vertical wind |
---|
75 | ! Langevin equation for the vertical wind component |
---|
76 | ! ioutputforeachrelease Should each release be a seperate output field? |
---|
77 | ! iflux flux calculation options: 1 calculation of fluxes, 2 no fluxes |
---|
78 | ! iout output options: 1 conc. output (ng/m3), 2 mixing ratio (pptv), 3 both |
---|
79 | ! ipout particle dump options: 0 no, 1 every output interval, 2 only at end |
---|
80 | ! ipin read in particle positions from dumped file from a previous run |
---|
81 | ! fine real(ifine) |
---|
82 | ! mdomainfill 0: normal run |
---|
83 | ! 1: particles are initialized according to atmospheric mass distribution |
---|
84 | ! ind_source switches between different units for concentrations at the source |
---|
85 | ! NOTE that in backward simulations the release of computational particles |
---|
86 | ! takes place at the "receptor" and the sampling of particles at the "source". |
---|
87 | ! 1= mass units |
---|
88 | ! 2= mass mixing ratio units |
---|
89 | ! ind_receptor switches between different units for FLEXPART concentration at the receptor |
---|
90 | ! 1= mass units |
---|
91 | ! 2= mass mixing ratio units |
---|
92 | ! linit_cond switch on the output of sensitivity to initial conditions for backward runs |
---|
93 | ! 0=no, 1=mass unit, 2=mass mixing ratio unit |
---|
94 | ! mquasilag 0: normal run |
---|
95 | ! 1: Particle position output is produced in a condensed format and particles are numbered |
---|
96 | ! surf_only switch output in grid_time files for surface only or full vertical resolution |
---|
97 | ! 0=no (full vertical resolution), 1=yes (surface only) |
---|
98 | ! nested_output: 0 no, 1 yes |
---|
99 | ! turbswitch determines how the Markov chain is formulated |
---|
100 | |
---|
101 | ! ind_rel and ind_samp are used within the code to change between mass and mass-mix (see readcommand.f) |
---|
102 | |
---|
103 | |
---|
104 | integer :: mintime,itsplit |
---|
105 | |
---|
106 | ! mintime minimum time step to be used by FLEXPART |
---|
107 | ! itsplit time constant for splitting particles |
---|
108 | |
---|
109 | integer :: lsubgrid,lconvection,lagespectra |
---|
110 | |
---|
111 | ! lsubgrid 1 if subgrid topography parameterization switched on, 2 if not |
---|
112 | ! lconvection 1 if convection parameterization switched on, 0 if not |
---|
113 | ! lagespectra 1 if age spectra calculation switched on, 2 if not |
---|
114 | |
---|
115 | |
---|
116 | integer :: nageclass,lage(maxageclass) |
---|
117 | |
---|
118 | ! nageclass number of ageclasses for the age spectra calculation |
---|
119 | ! lage [s] ageclasses for the age spectra calculation |
---|
120 | |
---|
121 | |
---|
122 | logical :: gdomainfill |
---|
123 | |
---|
124 | ! gdomainfill .T., if domain-filling is global, .F. if not |
---|
125 | |
---|
126 | |
---|
127 | |
---|
128 | !********************************************************************* |
---|
129 | ! Variables defining the release locations, released species and their |
---|
130 | ! properties, etc. |
---|
131 | !********************************************************************* |
---|
132 | |
---|
133 | !change Sabine Eckhardt, only save the first 1000 identifier for releasepoints |
---|
134 | character :: compoint(1001)*45 |
---|
135 | integer :: numpoint |
---|
136 | !sec, now dynamically allocated: |
---|
137 | ! ireleasestart(maxpoint),ireleaseend(maxpoint) |
---|
138 | ! real xpoint1(maxpoint),ypoint1(maxpoint) |
---|
139 | !real xpoint2(maxpoint),ypoint2(maxpoint) |
---|
140 | !real zpoint1(maxpoint),zpoint2(maxpoint) |
---|
141 | !integer*2 kindz(maxpoint) |
---|
142 | integer :: specnum(maxspec) |
---|
143 | !real xmass(maxpoint,maxspec) |
---|
144 | real :: decay(maxspec) |
---|
145 | real :: weta(maxspec),wetb(maxspec) |
---|
146 | ! NIK: 31.01.2013- parameters for in-cloud scavening |
---|
147 | real :: weta_in(maxspec), wetb_in(maxspec), wetc_in(maxspec), wetd_in(maxspec) |
---|
148 | real :: reldiff(maxspec),henry(maxspec),f0(maxspec) |
---|
149 | real :: density(maxspec),dquer(maxspec),dsigma(maxspec) |
---|
150 | real :: vsetaver(maxspec),cunningham(maxspec),weightmolar(maxspec) |
---|
151 | real :: vset(maxspec,ni),schmi(maxspec,ni),fract(maxspec,ni) |
---|
152 | real :: ri(5,numclass),rac(5,numclass),rcl(maxspec,5,numclass) |
---|
153 | real :: rgs(maxspec,5,numclass),rlu(maxspec,5,numclass) |
---|
154 | real :: rm(maxspec),dryvel(maxspec),kao(maxspec),ohreact(maxspec) |
---|
155 | ! se it is possible to associate a species with a second one to make transfer from gas to aerosol |
---|
156 | integer :: spec_ass(maxspec) |
---|
157 | |
---|
158 | real :: area_hour(maxspec,24),point_hour(maxspec,24) |
---|
159 | real :: area_dow(maxspec,7),point_dow(maxspec,7) |
---|
160 | |
---|
161 | !integer npart(maxpoint) |
---|
162 | integer :: nspec,maxpointspec_act |
---|
163 | character(len=10) :: species(maxspec) |
---|
164 | |
---|
165 | |
---|
166 | ! compoint comment, also "name" of each starting point |
---|
167 | ! numpoint actual number of trajectory starting/ending points |
---|
168 | ! ireleasestart,ireleaseend [s] starting and ending time of each release |
---|
169 | ! xmass total mass emitted |
---|
170 | ! xpoint1,ypoint1 lower left coordinates of release area |
---|
171 | ! xpoint2,ypoint2 upper right coordinates of release area |
---|
172 | ! zpoint1,zpoint2 min./max. z-coordinates of release points |
---|
173 | ! kindz 1: zpoint is in m agl, 2: zpoint is in m asl |
---|
174 | ! npart number of particles per release point |
---|
175 | ! nspec number of different species allowed for one release |
---|
176 | ! maxpointspec_act number of releaspoints for which a different output shall be created |
---|
177 | ! species name of species |
---|
178 | ! decay decay constant of radionuclide |
---|
179 | |
---|
180 | ! WET DEPOSITION |
---|
181 | ! weta, wetb parameters for determining below-cloud wet scavenging coefficients |
---|
182 | ! weta_in, wetb_in parameters for determining in-cloud wet scavenging coefficients |
---|
183 | ! wetc_in, wetd_in parameters for determining in-cloud wet scavenging coefficients |
---|
184 | |
---|
185 | ! GAS DEPOSITION |
---|
186 | ! reldiff diffusivitiy of species relative to diff. of H2O |
---|
187 | ! henry [M/atm] Henry constant |
---|
188 | ! f0 reactivity relative to that of O3 |
---|
189 | ! ri [s/m] stomatal resistance |
---|
190 | ! rcl [s/m] lower canopy resistance |
---|
191 | ! rgs [s/m] ground resistance |
---|
192 | ! rlu [s/m] leaf cuticular resistance |
---|
193 | ! rm [s/m] mesophyll resistance |
---|
194 | ! dryvel [m/s] constant dry deposition velocity |
---|
195 | |
---|
196 | ! PARTICLE DEPOSITION |
---|
197 | ! density [kg/m3] density of particles |
---|
198 | ! dquer [m] mean diameter of particles |
---|
199 | ! dsigma dsigma=10 or dsigma=0.1 means that 68% of the |
---|
200 | ! mass are between 0.1*dquer and 10*dquer |
---|
201 | |
---|
202 | ! fract mass fraction of each diameter interval |
---|
203 | ! vset [m/s] gravitational settling velocity in ni intervals |
---|
204 | ! cunningham Cunningham slip correction (strictly valid only near surface) |
---|
205 | ! vsetaver [m/s] average gravitational settling velocity |
---|
206 | ! schmi Schmidt number**2/3 of each diameter interval |
---|
207 | ! weightmolar [g/mol] molecular weight |
---|
208 | |
---|
209 | ! TIME VARIATION OF EMISSION |
---|
210 | ! area_hour, point_hour daily variation of emission strengths for area and point sources |
---|
211 | ! area_dow, point_dow day-of-week variation of emission strengths for area and point sources |
---|
212 | |
---|
213 | |
---|
214 | |
---|
215 | !********************************************************** |
---|
216 | ! Variables used for domain-filling trajectory calculations |
---|
217 | !********************************************************** |
---|
218 | |
---|
219 | integer :: nx_we(2),ny_sn(2) |
---|
220 | integer :: numcolumn |
---|
221 | integer :: numcolumn_we(2,0:nymax-1),numcolumn_sn(2,0:nxmax-1) |
---|
222 | real :: zcolumn_we(2,0:nymax-1,maxcolumn) |
---|
223 | real :: zcolumn_sn(2,0:nxmax-1,maxcolumn) |
---|
224 | real :: xmassperparticle |
---|
225 | real :: acc_mass_we(2,0:nymax-1,maxcolumn) |
---|
226 | real :: acc_mass_sn(2,0:nxmax-1,maxcolumn) |
---|
227 | |
---|
228 | ! nx_we(2) x indices of western and eastern boundary of domain-filling |
---|
229 | ! ny_sn(2) y indices of southern and northern boundary of domain-filling |
---|
230 | ! numcolumn_we number of particles to be released within one column |
---|
231 | ! at the western and eastern boundary surfaces |
---|
232 | ! numcolumn_sn same as numcolumn_we, but for southern and northern domain boundary |
---|
233 | ! numcolumn maximum number of particles to be released within a single |
---|
234 | ! column |
---|
235 | ! zcolumn_we altitudes where particles are to be released |
---|
236 | ! at the western and eastern boundary surfaces |
---|
237 | ! zcolumn_sn same as zcolumn_we, but for southern and northern domain boundary |
---|
238 | ! xmassperparticle air mass per particle in the domain-filling traj. option |
---|
239 | ! acc_mass_we mass that has accumulated at the western and eastern boundary; |
---|
240 | ! if it exceeds xmassperparticle, a particle is released and |
---|
241 | ! acc_mass_we is reduced accordingly |
---|
242 | ! acc_mass_sn same as acc_mass_we, but for southern and northern domain boundary |
---|
243 | |
---|
244 | |
---|
245 | |
---|
246 | !****************************************************************************** |
---|
247 | ! Variables associated with the ECMWF meteorological input data ("wind fields") |
---|
248 | !****************************************************************************** |
---|
249 | |
---|
250 | integer :: numbwf,wftime(maxwf),lwindinterv |
---|
251 | character(len=255) :: wfname(maxwf),wfspec(maxwf) |
---|
252 | |
---|
253 | ! lwindinterv [s] Interval between wind fields currently in memory |
---|
254 | ! numbwf actual number of wind fields |
---|
255 | ! wftime(maxwf) [s] times relative to beginning time of wind fields |
---|
256 | ! wfname(maxwf) file names of wind fields |
---|
257 | ! wfspec(maxwf) specifications of wind field file, e.g. if on hard |
---|
258 | ! disc or on tape |
---|
259 | |
---|
260 | integer :: memtime(2),memind(2) |
---|
261 | |
---|
262 | ! memtime [s] validation times of wind fields in memory |
---|
263 | ! memind pointer to wind field, in order to avoid shuffling |
---|
264 | ! of wind fields |
---|
265 | |
---|
266 | |
---|
267 | |
---|
268 | !**************************************************************************** |
---|
269 | ! Variables defining actual size and geographical location of the wind fields |
---|
270 | !**************************************************************************** |
---|
271 | |
---|
272 | integer :: nx,ny,nxmin1,nymin1,nxfield,nuvz,nwz,nz,nmixz,nlev_ec |
---|
273 | real :: dx,dy,xlon0,ylat0,dxconst,dyconst,height(nzmax) |
---|
274 | |
---|
275 | ! nx,ny,nz actual dimensions of wind fields in x,y and z |
---|
276 | ! direction, respectively |
---|
277 | ! nxmin1,nymin1 nx-1, ny-1, respectively |
---|
278 | ! nuvz,nwz vertical dimension of original ECMWF data |
---|
279 | ! nxfield same as nx for limited area fields, |
---|
280 | ! but for global fields nx=nxfield+1 |
---|
281 | ! nmixz number of levels up to maximum PBL height (3500 m) |
---|
282 | |
---|
283 | ! nuvz is used for u,v components |
---|
284 | ! nwz is used for w components (staggered grid) |
---|
285 | ! nz is used for the levels in transformed coordinates (terrain-following Cartesian |
---|
286 | ! coordinates) |
---|
287 | |
---|
288 | ! nlev_ec number of levels ECMWF model |
---|
289 | ! dx grid distance in x direction |
---|
290 | ! dy grid distance in y direction |
---|
291 | ! dxconst,dyconst auxiliary variables for utransform,vtransform |
---|
292 | ! height heights of all levels |
---|
293 | ! xlon0 geographical longitude and |
---|
294 | ! ylat0 geographical latitude of lower left grid point |
---|
295 | |
---|
296 | |
---|
297 | |
---|
298 | !************************************************* |
---|
299 | ! Variables used for vertical model discretization |
---|
300 | !************************************************* |
---|
301 | |
---|
302 | real :: akm(nwzmax),bkm(nwzmax) |
---|
303 | real :: akz(nuvzmax),bkz(nuvzmax) |
---|
304 | real :: aknew(nzmax),bknew(nzmax) |
---|
305 | |
---|
306 | ! akm,bkm: coeffizients which regulate vertical discretization of ecmwf model |
---|
307 | ! (at the border of model layers) |
---|
308 | ! akz,bkz: model discretization coeffizients at the centre of the layers |
---|
309 | ! aknew,bknew model discretization coeffizients at the interpolated levels |
---|
310 | |
---|
311 | |
---|
312 | |
---|
313 | ! Fixed fields, unchangeable with time |
---|
314 | !************************************* |
---|
315 | |
---|
316 | real :: oro(0:nxmax-1,0:nymax-1) |
---|
317 | real :: excessoro(0:nxmax-1,0:nymax-1) |
---|
318 | real :: lsm(0:nxmax-1,0:nymax-1) |
---|
319 | real :: xlanduse(0:nxmax-1,0:nymax-1,numclass) |
---|
320 | |
---|
321 | ! oro [m] orography of the ECMWF model |
---|
322 | ! excessoro excess orography mother domain |
---|
323 | ! lsm land sea mask of the ECMWF model |
---|
324 | ! xlanduse [0-1] area fractions in percent |
---|
325 | |
---|
326 | ! 3d fields |
---|
327 | !********** |
---|
328 | |
---|
329 | real :: uu(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
330 | real :: vv(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
331 | real :: uupol(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
332 | real :: vvpol(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
333 | real :: ww(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
334 | real :: tt(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
335 | real :: qv(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
336 | real :: pv(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
337 | real :: rho(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
338 | real :: drhodz(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
339 | real :: tth(0:nxmax-1,0:nymax-1,nuvzmax,2) |
---|
340 | real :: qvh(0:nxmax-1,0:nymax-1,nuvzmax,2) |
---|
341 | real :: pplev(0:nxmax-1,0:nymax-1,nuvzmax,2) |
---|
342 | !scavenging NIK, PS |
---|
343 | integer(kind=1) :: clouds(0:nxmax-1,0:nymax-1,nzmax,2) |
---|
344 | integer :: cloudsh(0:nxmax-1,0:nymax-1,2) |
---|
345 | integer icloudbot(0:nxmax-1,0:nymax-1,2) |
---|
346 | integer icloudthck(0:nxmax-1,0:nymax-1,2) |
---|
347 | |
---|
348 | |
---|
349 | ! uu,vv,ww [m/2] wind components in x,y and z direction |
---|
350 | ! uupol,vvpol [m/s] wind components in polar stereographic projection |
---|
351 | ! tt [K] temperature data |
---|
352 | ! qv specific humidity data |
---|
353 | ! pv (pvu) potential vorticity |
---|
354 | ! rho [kg/m3] air density |
---|
355 | ! drhodz [kg/m2] vertical air density gradient |
---|
356 | ! tth,qvh tth,qvh on original eta levels |
---|
357 | ! clouds: no cloud, no precipitation 0 |
---|
358 | ! cloud, no precipitation 1 |
---|
359 | ! rainout conv/lsp dominated 2/3 |
---|
360 | ! washout conv/lsp dominated 4/5 |
---|
361 | ! PS 2013 |
---|
362 | !c icloudbot (m) cloud bottom height |
---|
363 | !c icloudthck (m) cloud thickness |
---|
364 | |
---|
365 | ! pplev for the GFS version |
---|
366 | |
---|
367 | ! 2d fields |
---|
368 | !********** |
---|
369 | |
---|
370 | real :: ps(0:nxmax-1,0:nymax-1,1,2) |
---|
371 | real :: sd(0:nxmax-1,0:nymax-1,1,2) |
---|
372 | real :: msl(0:nxmax-1,0:nymax-1,1,2) |
---|
373 | real :: tcc(0:nxmax-1,0:nymax-1,1,2) |
---|
374 | real :: u10(0:nxmax-1,0:nymax-1,1,2) |
---|
375 | real :: v10(0:nxmax-1,0:nymax-1,1,2) |
---|
376 | real :: tt2(0:nxmax-1,0:nymax-1,1,2) |
---|
377 | real :: td2(0:nxmax-1,0:nymax-1,1,2) |
---|
378 | real :: lsprec(0:nxmax-1,0:nymax-1,1,2) |
---|
379 | real :: convprec(0:nxmax-1,0:nymax-1,1,2) |
---|
380 | real :: sshf(0:nxmax-1,0:nymax-1,1,2) |
---|
381 | real :: ssr(0:nxmax-1,0:nymax-1,1,2) |
---|
382 | real :: surfstr(0:nxmax-1,0:nymax-1,1,2) |
---|
383 | real :: ustar(0:nxmax-1,0:nymax-1,1,2) |
---|
384 | real :: wstar(0:nxmax-1,0:nymax-1,1,2) |
---|
385 | real :: hmix(0:nxmax-1,0:nymax-1,1,2) |
---|
386 | real :: tropopause(0:nxmax-1,0:nymax-1,1,2) |
---|
387 | real :: oli(0:nxmax-1,0:nymax-1,1,2) |
---|
388 | real :: diffk(0:nxmax-1,0:nymax-1,1,2) |
---|
389 | |
---|
390 | ! ps surface pressure |
---|
391 | ! sd snow depth |
---|
392 | ! msl mean sea level pressure |
---|
393 | ! tcc total cloud cover |
---|
394 | ! u10 10 meter u |
---|
395 | ! v10 10 meter v |
---|
396 | ! tt2 2 meter temperature |
---|
397 | ! td2 2 meter dew point |
---|
398 | ! lsprec [mm/h] large scale total precipitation |
---|
399 | ! convprec [mm/h] convective precipitation |
---|
400 | ! sshf surface sensible heat flux |
---|
401 | ! ssr surface solar radiation |
---|
402 | ! surfstr surface stress |
---|
403 | ! ustar [m/s] friction velocity |
---|
404 | ! wstar [m/s] convective velocity scale |
---|
405 | ! hmix [m] mixing height |
---|
406 | ! tropopause [m] altitude of thermal tropopause |
---|
407 | ! oli [m] inverse Obukhov length (1/L) |
---|
408 | ! diffk [m2/s] diffusion coefficient at reference height |
---|
409 | |
---|
410 | |
---|
411 | real :: vdep(0:nxmax-1,0:nymax-1,maxspec,2) |
---|
412 | |
---|
413 | ! vdep [m/s] deposition velocities |
---|
414 | |
---|
415 | |
---|
416 | !******************************************************************** |
---|
417 | ! Variables associated with the ECMWF input data (nested wind fields) |
---|
418 | !******************************************************************** |
---|
419 | |
---|
420 | ! NOTE: all nested variables have the same name as the variables used |
---|
421 | ! for the mother domain, except with a 'n' appended at the end |
---|
422 | !******************************************************************** |
---|
423 | |
---|
424 | integer :: numbnests |
---|
425 | |
---|
426 | ! numbnests number of nested grids |
---|
427 | |
---|
428 | character(len=255) :: wfnamen(maxnests,maxwf) |
---|
429 | character(len=18) :: wfspecn(maxnests,maxwf) |
---|
430 | |
---|
431 | ! wfnamen nested wind field names |
---|
432 | ! wfspecn specifications of wind field file, e.g. if on hard |
---|
433 | ! disc or on tape |
---|
434 | |
---|
435 | |
---|
436 | !********************************************************************* |
---|
437 | ! Variables characterizing size and location of the nested wind fields |
---|
438 | !********************************************************************* |
---|
439 | |
---|
440 | integer :: nxn(maxnests),nyn(maxnests) |
---|
441 | real :: dxn(maxnests),dyn(maxnests),xlon0n(maxnests),ylat0n(maxnests) |
---|
442 | |
---|
443 | ! nxn,nyn actual dimensions of nested wind fields in x and y direction |
---|
444 | ! dxn,dyn grid distances in x,y direction for the nested grids |
---|
445 | ! xlon0n geographical longitude of lower left grid point of nested wind fields |
---|
446 | ! ylat0n geographical latitude of lower left grid point of nested wind fields |
---|
447 | |
---|
448 | |
---|
449 | ! Nested fields, unchangeable with time |
---|
450 | !************************************** |
---|
451 | |
---|
452 | real :: oron(0:nxmaxn-1,0:nymaxn-1,maxnests) |
---|
453 | real :: excessoron(0:nxmaxn-1,0:nymaxn-1,maxnests) |
---|
454 | real :: lsmn(0:nxmaxn-1,0:nymaxn-1,maxnests) |
---|
455 | real :: xlandusen(0:nxmaxn-1,0:nymaxn-1,numclass,maxnests) |
---|
456 | |
---|
457 | |
---|
458 | ! 3d nested fields |
---|
459 | !***************** |
---|
460 | |
---|
461 | real :: uun(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
462 | real :: vvn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
463 | real :: wwn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
464 | real :: ttn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
465 | real :: qvn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
466 | real :: pvn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
467 | integer(kind=1) :: cloudsn(0:nxmaxn-1,0:nymaxn-1,0:nzmax,2,maxnests) |
---|
468 | integer :: cloudsnh(0:nxmaxn-1,0:nymaxn-1,2,maxnests) |
---|
469 | real :: rhon(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
470 | real :: drhodzn(0:nxmaxn-1,0:nymaxn-1,nzmax,2,maxnests) |
---|
471 | real :: tthn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,2,maxnests) |
---|
472 | real :: qvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,2,maxnests) |
---|
473 | |
---|
474 | ! 2d nested fields |
---|
475 | !***************** |
---|
476 | |
---|
477 | real :: psn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
478 | real :: sdn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
479 | real :: msln(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
480 | real :: tccn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
481 | real :: u10n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
482 | real :: v10n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
483 | real :: tt2n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
484 | real :: td2n(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
485 | real :: lsprecn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
486 | real :: convprecn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
487 | real :: sshfn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
488 | real :: ssrn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
489 | real :: surfstrn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
490 | real :: ustarn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
491 | real :: wstarn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
492 | real :: hmixn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
493 | real :: tropopausen(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
494 | real :: olin(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
495 | real :: diffkn(0:nxmaxn-1,0:nymaxn-1,1,2,maxnests) |
---|
496 | real :: vdepn(0:nxmaxn-1,0:nymaxn-1,maxspec,2,maxnests) |
---|
497 | |
---|
498 | |
---|
499 | !************************************************* |
---|
500 | ! Certain auxiliary variables needed for the nests |
---|
501 | !************************************************* |
---|
502 | |
---|
503 | real :: xresoln(0:maxnests),yresoln(0:maxnests) |
---|
504 | |
---|
505 | ! xresoln, yresoln Factors by which the resolutions in the nests |
---|
506 | ! are enhanced compared to mother grid |
---|
507 | |
---|
508 | real :: xln(maxnests),yln(maxnests),xrn(maxnests),yrn(maxnests) |
---|
509 | |
---|
510 | ! xln,yln,xrn,yrn Corner points of nested grids in grid coordinates |
---|
511 | ! of mother grid |
---|
512 | |
---|
513 | |
---|
514 | !****************************************************** |
---|
515 | ! Variables defining the polar stereographic projection |
---|
516 | !****************************************************** |
---|
517 | |
---|
518 | logical :: xglobal,sglobal,nglobal |
---|
519 | real :: switchnorthg,switchsouthg |
---|
520 | |
---|
521 | !xglobal T for global fields, F for limited area fields |
---|
522 | !sglobal T if domain extends towards south pole |
---|
523 | !nglobal T if domain extends towards north pole |
---|
524 | !switchnorthg,switchsouthg same as parameters switchnorth, |
---|
525 | ! switchsouth, but in grid units |
---|
526 | |
---|
527 | real :: southpolemap(9),northpolemap(9) |
---|
528 | |
---|
529 | !southpolemap,northpolemap define stereographic projections |
---|
530 | ! at the two poles |
---|
531 | |
---|
532 | |
---|
533 | !****************** |
---|
534 | ! Landuse inventory |
---|
535 | ! Sabine Eckhardt Dec 06: change to new landuse inventary - 11 classes, 1200 x 600 global |
---|
536 | !****************** |
---|
537 | |
---|
538 | integer(kind=1) :: landinvent(1200,600,6) |
---|
539 | real :: z0(numclass) |
---|
540 | |
---|
541 | ! landinvent landuse inventory (numclass=11 classes) |
---|
542 | ! z0 roughness length for the landuse classes |
---|
543 | |
---|
544 | |
---|
545 | |
---|
546 | !************************************************************************** |
---|
547 | ! Variables characterizing the output grid and containing the model results |
---|
548 | !************************************************************************** |
---|
549 | |
---|
550 | integer :: numxgrid,numygrid,numzgrid |
---|
551 | real :: dxout,dyout,outlon0,outlat0,xoutshift,youtshift |
---|
552 | integer :: numxgridn,numygridn |
---|
553 | real :: dxoutn,dyoutn,outlon0n,outlat0n,xoutshiftn,youtshiftn |
---|
554 | !real outheight(maxzgrid),outheighthalf(maxzgrid) |
---|
555 | logical :: DEP,DRYDEP,DRYDEPSPEC(maxspec),WETDEP,OHREA,ASSSPEC |
---|
556 | |
---|
557 | ! numxgrid,numygrid number of grid points in x,y-direction |
---|
558 | ! numxgridn,numygridn number of grid points in x,y-direction for nested output grid |
---|
559 | ! numzgrid number of vertical levels of output grid |
---|
560 | ! dxout,dyout grid distance of output grid |
---|
561 | ! dxoutn,dyoutn grid distance of nested output grid |
---|
562 | ! outlon0,outlat0 lower left corner of output grid |
---|
563 | ! outlon0n,outlat0n lower left corner of nested output grid |
---|
564 | ! xoutshift,youtshift xlon0-outlon0, ylat0-outlat0 |
---|
565 | ! xoutshiftn,youtshiftn xlon0-outlon0n, ylat0-outlat0n |
---|
566 | ! outheight [m] upper levels of the output grid |
---|
567 | ! outheighthalf [m] half (middle) levels of the output grid cells |
---|
568 | ! DEP .true., if either dry or wet depos. is switched on |
---|
569 | ! DRYDEP .true., if dry deposition is switched on |
---|
570 | ! DRYDEPSPEC .true., if dry deposition is switched on for that species |
---|
571 | ! WETDEP .true., if wet deposition is switched on |
---|
572 | ! OHREA .true., if OH reaction is switched on |
---|
573 | ! ASSSPEC .true., if there are two species asscoiated |
---|
574 | ! (i.e. transfer of mass between these two occurs |
---|
575 | |
---|
576 | |
---|
577 | |
---|
578 | ! if output for each releasepoint shall be created maxpointspec=number of releasepoints |
---|
579 | ! else maxpointspec is 1 -> moved to unc_mod |
---|
580 | ! the OUTGRID is moved to the module outg_mod |
---|
581 | !****************************************************************************** |
---|
582 | |
---|
583 | !real gridunc(0:maxxgrid-1,0:maxygrid-1,maxzgrid,maxspec, |
---|
584 | ! + maxpointspec_act,nclassunc,maxageclass) |
---|
585 | !real griduncn(0:maxxgridn-1,0:maxygridn-1,maxzgrid,maxspec, |
---|
586 | ! + maxpointspec_act,nclassunc,maxageclass) |
---|
587 | !real wetgridunc(0:maxxgrid-1,0:maxygrid-1,maxspec, |
---|
588 | ! + maxpointspec_act,nclassunc,maxageclass) |
---|
589 | !real wetgriduncn(0:maxxgridn-1,0:maxygridn-1,maxspec, |
---|
590 | ! +ct maxpointspec,nclassunc,maxageclass) |
---|
591 | !real drygridunc(0:maxxgrid-1,0:maxygrid-1,maxspec,maxpointspec, |
---|
592 | ! + nclassunc,maxageclass) |
---|
593 | !real drygriduncn(0:maxxgridn-1,0:maxygridn-1,maxspec, |
---|
594 | ! + maxpointspec,nclassunc,maxageclass) |
---|
595 | |
---|
596 | !real oroout(0:maxxgrid-1,0:maxygrid-1) |
---|
597 | !real orooutn(0:maxxgridn-1,0:maxygridn-1) |
---|
598 | ! real area(0:maxxgrid-1,0:maxygrid-1) |
---|
599 | !real arean(0:maxxgridn-1,0:maxygridn-1) |
---|
600 | !real volume(0:maxxgrid-1,0:maxygrid-1,maxzgrid) |
---|
601 | !real volumen(0:maxxgridn-1,0:maxygridn-1,maxzgrid) |
---|
602 | |
---|
603 | !real areaeast(0:maxxgrid-1,0:maxygrid-1,maxzgrid) |
---|
604 | !real areanorth(0:maxxgrid-1,0:maxygrid-1,maxzgrid) |
---|
605 | |
---|
606 | |
---|
607 | ! gridunc,griduncn uncertainty of outputted concentrations |
---|
608 | ! wetgridunc,wetgriduncn uncertainty of accumulated wet deposited mass on output grid |
---|
609 | ! drygridunc,drygriduncn uncertainty of accumulated dry deposited mass on output grid |
---|
610 | ! oroout,orooutn [m] height of model topography at output grid |
---|
611 | ! area,arean [m2] area of each grid cell |
---|
612 | ! volume,volumen [m3] volume of each grid cell |
---|
613 | ! ... field names with n at the end indicate a nested output grid |
---|
614 | |
---|
615 | |
---|
616 | !*********************************** |
---|
617 | ! Variables defining receptor points |
---|
618 | !*********************************** |
---|
619 | |
---|
620 | real :: xreceptor(maxreceptor),yreceptor(maxreceptor) |
---|
621 | real :: receptorarea(maxreceptor) |
---|
622 | real :: creceptor(maxreceptor,maxspec) |
---|
623 | character(len=16) :: receptorname(maxreceptor) |
---|
624 | integer :: numreceptor |
---|
625 | |
---|
626 | ! xreceptor,yreceptor receptor position |
---|
627 | ! creceptor concentrations at receptor points |
---|
628 | ! receptorarea area of 1*1 grid cell at receptor point |
---|
629 | |
---|
630 | |
---|
631 | |
---|
632 | !*************************************** |
---|
633 | ! Variables characterizing each particle |
---|
634 | !*************************************** |
---|
635 | |
---|
636 | integer :: numpart,itra1(maxpart) |
---|
637 | integer :: npoint(maxpart),nclass(maxpart) |
---|
638 | integer :: idt(maxpart),itramem(maxpart),itrasplit(maxpart) |
---|
639 | integer :: numparticlecount |
---|
640 | |
---|
641 | real(kind=dp) :: xtra1(maxpart),ytra1(maxpart) |
---|
642 | real :: ztra1(maxpart),xmass1(maxpart,maxspec) |
---|
643 | |
---|
644 | ! numpart actual number of particles in memory |
---|
645 | ! itra1 (maxpart) [s] temporal positions of the particles |
---|
646 | ! npoint(maxpart) indicates the release point of each particle |
---|
647 | ! nclass (maxpart) one of nclassunc classes to which the particle is attributed |
---|
648 | ! itramem (maxpart) [s] memorized release times of the particles |
---|
649 | ! itrasplit (maxpart) [s] next time when particle is to be split into two |
---|
650 | ! idt(maxpart) [s] time step to be used for next integration |
---|
651 | ! numparticlecount counts the total number of particles that have been released |
---|
652 | ! xtra1,ytra1,ztra1 spatial positions of the particles |
---|
653 | ! xmass1 [kg] particle masses |
---|
654 | |
---|
655 | |
---|
656 | |
---|
657 | !******************************************************* |
---|
658 | ! Info table on available chemical species/radionuclides |
---|
659 | !******************************************************* |
---|
660 | |
---|
661 | !character*10 specname(maxtable) |
---|
662 | !real decaytime(maxtable),wetscava(maxtable),wetscavb(maxtable) |
---|
663 | !real drydiff(maxtable),dryhenry(maxtable),dryactiv(maxtable) |
---|
664 | !real partrho(maxtable),partmean(maxtable),partsig(maxtable) |
---|
665 | !real dryvelo(maxtable),weightmol(maxtable),ohreact(maxtable) |
---|
666 | |
---|
667 | ! specname Name of chemical species/radionuclide |
---|
668 | ! decaytime Half time of radionuclides |
---|
669 | ! wetscava, wetscavb Parameters for calculating scavenging coefficients |
---|
670 | ! drydiff diffusivitiy of species relative to diff. of H2O |
---|
671 | ! dryhenry [M/atm] Henry constant |
---|
672 | ! dryactiv reactivity relative to that of O3 |
---|
673 | ! partrho [kg/m3] density of particles |
---|
674 | ! partmean [m] mean diameter of particles |
---|
675 | ! partsig [m] mean stand. deviation of particle diameter |
---|
676 | ! dryvelo [cm/s] constant dry deposition velocity |
---|
677 | ! weightmol [g/mol] molecular weight |
---|
678 | ! ohreact OH reaction rate |
---|
679 | |
---|
680 | |
---|
681 | !******************** |
---|
682 | ! Random number field |
---|
683 | !******************** |
---|
684 | |
---|
685 | real :: rannumb(maxrand) |
---|
686 | |
---|
687 | ! rannumb field of normally distributed random numbers |
---|
688 | |
---|
689 | !******************** |
---|
690 | ! Verbosity, testing flags |
---|
691 | !******************** |
---|
692 | integer :: verbosity=0 |
---|
693 | integer :: info_flag=0 |
---|
694 | INTEGER :: count_clock, count_clock0, count_rate, count_max |
---|
695 | |
---|
696 | |
---|
697 | end module com_mod |
---|