source: flexpart.git/src/com_mod.f90 @ 5f2e8f6

flexpart-noresm
Last change on this file since 5f2e8f6 was 5f2e8f6, checked in by Ignacio Pisso <Ignacio.Pisso@…>, 8 years ago

new flexpart noresm code in src

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