source: flexpart.git/src/com_mod.f90 @ 41d8574

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

bugfix: MPI version gave wrong wet deposition when using ECMWF cloud water fields. Cloud water in ECMWF fields now uses parameter qc, or reads clwc+ciwc. Added minmass variable as limit for terminating particles.

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