source: branches/petra/src/com_mod.f90

Last change on this file was 37, checked in by pesei, 9 years ago

Wet dep quick fix and other small changes. Wet depo quick fix not final yet.

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