source: flexpart.git/src/com_mod.f90 @ fddc6ec

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since fddc6ec was fddc6ec, checked in by Espen Sollum ATMOS <eso@…>, 8 years ago

Added a version number string for flexpart version, that will also be used for SPECIES file names. TODO: update unit tests, species and readspecies (master branch?)

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