source: flexpart.git/src/com_mod.f90 @ 8a65cb0

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

Added code, makefile for dev branch

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