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

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

Updates to Henrik's wet depo scheme

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