source: flexpart.git/src/com_mod.f90 @ 660bcb7

NetCDF
Last change on this file since 660bcb7 was 660bcb7, checked in by Anne Fouilloux <annefou@…>, 9 years ago

NETCDF outputs from svn trunk (hasod: ADD: netcdf module file)
I did not take changes in advance.f90; it will be added later.
I also changed OPENs where status was set to new and access is set to APPEND (had problems on abel.uio.no with intel compilers 2013.sp1.3)
It should contains technical changes only and results should be identical.

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