source: palm/trunk/SOURCE/mod_particle_attributes.f90 @ 3560

Last change on this file since 3560 was 3560, checked in by raasch, 5 years ago

bugfix to guarantee correct particle releases in case that the release interval is smaller than the model timestep

  • Property svn:keywords set to Id
File size: 16.8 KB
RevLine 
[1682]1!> @file mod_particle_attributes.f90
[2000]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1359]4!
[2000]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
[1359]9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
[2718]17! Copyright 1997-2018 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1359]19!
20! Current revisions:
21! ------------------
[2375]22!
23!
[1360]24! Former revisions:
25! -----------------
26! $Id: mod_particle_attributes.f90 3560 2018-11-23 09:20:21Z raasch $
[3560]27! time_prel replaced by last_particle_release_time
28!
29! 3405 2018-10-23 15:34:41Z raasch
[3405]30! bugfix: BIND attribute added to derived type particle_type
31!
32! 2718 2018-01-02 08:49:38Z maronga
[2716]33! Corrected "Former revisions" section
34!
35! 2696 2017-12-14 17:12:51Z kanani
36! Change in file header (GPL part)
37!
38! 2375 2017-08-29 14:10:28Z schwenkel
[2375]39! molecular_weight_of_solute, molecular_weight_of_water, vanthoff removed and
40! added in modules. Parameters are also used in bulk-microphysics.
41!
42! 2312 2017-07-14 20:26:51Z hoffmann
[2312]43! Aerosol initialization improved.
44!
45! 2305 2017-07-06 11:18:47Z hoffmann
[2305]46! Improved calculation of particle IDs.
[2312]47!
[2305]48! 2278 2017-06-12 13:08:18Z schwenkel
[2278]49! Added comments
[2312]50!
[2278]51! 2265 2017-06-08 16:58:28Z schwenkel
[2265]52! Unused variables removed.
[2312]53!
[2265]54! 2263 2017-06-08 14:59:01Z schwenkel
[2263]55! Implemented splitting and merging algorithm
[2312]56!
[2263]57! 2183 2017-03-17 14:29:15Z schwenkel
[1937]58!
[2183]59! 2182 2017-03-17 14:27:40Z schwenkel
60! Added parameters for simplified particle initialization.
[2312]61!
[2123]62! 2122 2017-01-18 12:22:54Z hoffmann
63! Calculation of particle ID
64! Particle attribute dvrp_psize renamed to user: this attribute can be used by
65! by the user to store any variable
66!
[2001]67! 2000 2016-08-20 18:09:15Z knoop
68! Forced header and separation lines into 80 columns
[2312]69!
[1937]70! 1936 2016-06-13 13:37:44Z suehring
71! +deallocate_memory, step_dealloc
72!
[1930]73! 1929 2016-06-09 16:25:25Z suehring
74! -sgs_wfu_par, sgs_wfv_par, sgs_wfw_par
75! + sgs_wf_par
[1360]76!
[1872]77! 1871 2016-04-15 11:46:09Z hoffmann
78! Initialization of aerosols added.
79!
[1851]80! 1849 2016-04-08 11:33:18Z hoffmann
81! bfactor, mass_of_solute, molecular_weight_of_solute, molecular_weight_of_water,
82! vanthoff added from modules
83!
[1832]84! 1831 2016-04-07 13:15:51Z hoffmann
85! palm_kernel removed, curvature_solution_effects added
86!
[1823]87! 1822 2016-04-07 07:49:42Z hoffmann
88! +collision_algorithm, all_or_nothing, average_impact
89! Tails removed.
90!
[1728]91! 1727 2015-11-20 07:22:02Z knoop
[2312]92! Bugfix: Cause of syntax warning gfortran preprocessor removed
93!
[1683]94! 1682 2015-10-07 23:56:08Z knoop
[2312]95! Code annotations made doxygen readable
[1683]96!
[1576]97! 1575 2015-03-27 09:56:27Z raasch
98! +seed_follows_topography
99!
[1360]100! 1359 2014-04-11 17:15:14Z hoffmann
[1359]101! new module containing all particle related variables
102! -dt_sort_particles
103!
104! Description:
105! ------------
[1682]106!> Definition of variables used to compute particle transport
[1359]107!------------------------------------------------------------------------------!
[1682]108MODULE particle_attributes
[1359]109
[3405]110    USE, INTRINSIC ::  ISO_C_BINDING
[2312]111
[1359]112    USE kinds
113
[2375]114    CHARACTER(LEN=15) ::  aero_species = 'nacl'                    !< aerosol species
115    CHARACTER(LEN=15) ::  aero_type    = 'maritime'                !< aerosol type
116    CHARACTER(LEN=15) ::  bc_par_lr    = 'cyclic'                  !< left/right boundary condition
117    CHARACTER(LEN=15) ::  bc_par_ns    = 'cyclic'                  !< north/south boundary condition
118    CHARACTER(LEN=15) ::  bc_par_b     = 'reflect'                 !< bottom boundary condition
119    CHARACTER(LEN=15) ::  bc_par_t     = 'absorb'                  !< top boundary condition
120    CHARACTER(LEN=15) ::  collision_kernel   = 'none'              !< collision kernel
[2312]121    CHARACTER(LEN=5)  ::  splitting_function = 'gamma'             !< function for calculation critical weighting factor
[2375]122    CHARACTER(LEN=5)  ::  splitting_mode     = 'const'             !< splitting mode
[1359]123
[2312]124    INTEGER(iwp) ::  deleted_particles = 0                        !< number of deleted particles per time step
[2265]125    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
[2263]126    INTEGER(iwp) ::  ibc_par_b                                    !< particle bottom boundary condition dummy
127    INTEGER(iwp) ::  ibc_par_lr                                   !< particle left/right boundary condition dummy
128    INTEGER(iwp) ::  ibc_par_ns                                   !< particle north/south boundary condition dummy
129    INTEGER(iwp) ::  ibc_par_t                                    !< particle top boundary condition dummy
130    INTEGER(iwp) ::  iran_part = -1234567                         !< number for random generator
131    INTEGER(iwp) ::  isf                                          !< dummy for splitting function
132    INTEGER(iwp) ::  i_splitting_mode                             !< dummy for splitting mode
[2278]133    INTEGER(iwp) ::  max_number_particles_per_gridbox = 100       !< namelist parameter (see documentation)
[2263]134    INTEGER(iwp) ::  merge_drp = 0                                !< number of merged droplets
[2312]135    INTEGER(iwp) ::  min_nr_particle = 50                         !< namelist parameter (see documentation)
[2263]136    INTEGER(iwp) ::  new_particles = 0                            !< number of new particles
[2312]137    INTEGER(iwp) ::  n_max = 100                                  !< number of radii bin for splitting functions
138    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)
139    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
140    INTEGER(iwp) ::  number_of_sublayers = 20                     !< number of sublayers for particle velocities betwenn surface and first grid level
141    INTEGER(iwp) ::  number_particles_per_gridbox = -1            !< namelist parameter (see documentation)
142    INTEGER(iwp) ::  offset_ocean_nzt = 0                         !< in case of oceans runs, the vertical index calculations need an offset
[2263]143    INTEGER(iwp) ::  offset_ocean_nzt_m1 = 0                      !< in case of oceans runs, the vertical index calculations need an offset
[2265]144    INTEGER(iwp) ::  particles_per_point = 1                      !< namelist parameter (see documentation)
145    INTEGER(iwp) ::  radius_classes = 20                          !< namelist parameter (see documentation)
[2263]146    INTEGER(iwp) ::  sort_count = 0                               !< counter for sorting particles
[2265]147    INTEGER(iwp) ::  splitting_factor = 2                         !< namelist parameter (see documentation)
148    INTEGER(iwp) ::  splitting_factor_max = 5                     !< namelist parameter (see documentation)
149    INTEGER(iwp) ::  step_dealloc = 100                           !< namelist parameter (see documentation)
[2263]150    INTEGER(iwp) ::  sum_merge_drp = 0                            !< sum of merged super droplets
151    INTEGER(iwp) ::  sum_new_particles = 0                        !< sum of created particles (in splitting algorithm)
[2312]152    INTEGER(iwp) ::  total_number_of_particles                    !< total number of particles in the whole model domain
[2263]153    INTEGER(iwp) ::  trlp_count_sum                               !< parameter for particle exchange of PEs
154    INTEGER(iwp) ::  trlp_count_recv_sum                          !< parameter for particle exchange of PEs
155    INTEGER(iwp) ::  trrp_count_sum                               !< parameter for particle exchange of PEs
156    INTEGER(iwp) ::  trrp_count_recv_sum                          !< parameter for particle exchange of PEs
157    INTEGER(iwp) ::  trsp_count_sum                               !< parameter for particle exchange of PEs
158    INTEGER(iwp) ::  trsp_count_recv_sum                          !< parameter for particle exchange of PEs
159    INTEGER(iwp) ::  trnp_count_sum                               !< parameter for particle exchange of PEs
160    INTEGER(iwp) ::  trnp_count_recv_sum                          !< parameter for particle exchange of PEs
[1359]161
[2263]162    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
[1359]163
[2263]164    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
[1359]165
[2312]166    LOGICAL ::  curvature_solution_effects = .FALSE.      !< namelist parameter (see documentation)
167    LOGICAL ::  deallocate_memory = .TRUE.                !< namelist parameter (see documentation)
[2263]168    LOGICAL ::  hall_kernel = .FALSE.                     !< flag for collision kernel
[2265]169    LOGICAL ::  merging = .FALSE.                         !< namelist parameter (see documentation)
[2263]170    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
[2312]171    LOGICAL ::  random_start_position = .FALSE.           !< namelist parameter (see documentation)
172    LOGICAL ::  read_particles_from_restartfile = .TRUE.  !< namelist parameter (see documentation)
[2265]173    LOGICAL ::  seed_follows_topography = .FALSE.         !< namelist parameter (see documentation)
174    LOGICAL ::  splitting = .FALSE.                       !< namelist parameter (see documentation)
[2263]175    LOGICAL ::  use_kernel_tables = .FALSE.               !< parameter, which turns on the use of precalculated collision kernels
[2312]176    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)
[2263]177    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
[2265]178    LOGICAL ::  write_particle_statistics = .FALSE.       !< namelist parameter (see documentation)
[2312]179
[1359]180    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
[2263]181                vertical_particle_advection = .TRUE.              !< Switch on/off vertical particle transport
[1359]182
[2312]183    REAL(wp) ::  aero_weight = 1.0_wp                      !< namelist parameter (see documentation)
[2265]184    REAL(wp) ::  alloc_factor = 20.0_wp                    !< namelist parameter (see documentation)
185    REAL(wp) ::  c_0 = 3.0_wp                              !< parameter for lagrangian timescale
186    REAL(wp) ::  dt_min_part = 0.0002_wp                   !< minimum particle time step when SGS velocities are used (s)
187    REAL(wp) ::  dt_prel = 9999999.9_wp                    !< namelist parameter (see documentation)
[2312]188    REAL(wp) ::  dt_write_particle_data = 9999999.9_wp     !< namelist parameter (see documentation)
189    REAL(wp) ::  end_time_prel = 9999999.9_wp              !< namelist parameter (see documentation)
[2265]190    REAL(wp) ::  initial_weighting_factor = 1.0_wp         !< namelist parameter (see documentation)
[3560]191    REAL(wp) ::  last_particle_release_time = 0.0_wp       !< last time of particle release
[2312]192    REAL(wp) ::  log_sigma(3) = 1.0_wp                     !< namelist parameter (see documentation)
193    REAL(wp) ::  na(3) = 0.0_wp                            !< namelist parameter (see documentation)
[2265]194    REAL(wp) ::  number_concentration = -1.0_wp            !< namelist parameter (see documentation)
195    REAL(wp) ::  particle_advection_start = 0.0_wp         !< namelist parameter (see documentation)
196    REAL(wp) ::  radius_merge = 1.0E-7_wp                  !< namelist parameter (see documentation)
197    REAL(wp) ::  radius_split = 40.0E-6_wp                 !< namelist parameter (see documentation)
[2312]198    REAL(wp) ::  rm(3) = 1.0E-6_wp                         !< namelist parameter (see documentation)
199    REAL(wp) ::  sgs_wf_part                               !< parameter for sgs
[2265]200    REAL(wp) ::  time_write_particle_data = 0.0_wp         !< write particle data at current time on file
201    REAL(wp) ::  weight_factor_merge = -1.0_wp             !< namelist parameter (see documentation)
202    REAL(wp) ::  weight_factor_split = -1.0_wp             !< namelist parameter (see documentation)
203    REAL(wp) ::  z0_av_global                              !< horizontal mean value of z0
[1359]204
[2265]205    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  density_ratio = 9999999.9_wp  !< namelist parameter (see documentation)
206    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdx = 9999999.9_wp            !< namelist parameter (see documentation)
207    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdy = 9999999.9_wp            !< namelist parameter (see documentation)
208    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdz = 9999999.9_wp            !< namelist parameter (see documentation)
209    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psb = 9999999.9_wp            !< namelist parameter (see documentation)
210    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psl = 9999999.9_wp            !< namelist parameter (see documentation)
211    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psn = 9999999.9_wp            !< namelist parameter (see documentation)
212    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psr = 9999999.9_wp            !< namelist parameter (see documentation)
213    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pss = 9999999.9_wp            !< namelist parameter (see documentation)
214    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pst = 9999999.9_wp            !< namelist parameter (see documentation).
215    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  radius = 9999999.9_wp         !< namelist parameter (see documentation)
[1359]216
[2263]217    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0   !< Precalculate LOG(z/z0)
[1359]218
[2312]219
[3405]220    TYPE, BIND(C) ::  particle_type
[2312]221        REAL(wp)     ::  aux1          !< auxiliary multi-purpose feature
222        REAL(wp)     ::  aux2          !< auxiliary multi-purpose feature
[2265]223        REAL(wp)     ::  radius        !< radius of particle
224        REAL(wp)     ::  age           !< age of particle
[2312]225        REAL(wp)     ::  age_m         !<
[2265]226        REAL(wp)     ::  dt_sum        !<
[2312]227        REAL(wp)     ::  e_m           !< interpolated sgs tke
[2265]228        REAL(wp)     ::  origin_x      !< origin x-position of particle (changed cyclic bc)
229        REAL(wp)     ::  origin_y      !< origin y-position of particle (changed cyclic bc)
230        REAL(wp)     ::  origin_z      !< origin z-position of particle (changed cyclic bc)
[2312]231        REAL(wp)     ::  rvar1         !<
[2265]232        REAL(wp)     ::  rvar2         !<
[2312]233        REAL(wp)     ::  rvar3         !<
[2265]234        REAL(wp)     ::  speed_x       !< speed of particle in x
235        REAL(wp)     ::  speed_y       !< speed of particle in y
236        REAL(wp)     ::  speed_z       !< speed of particle in z
[2312]237        REAL(wp)     ::  weight_factor !< weighting factor
238        REAL(wp)     ::  x             !< x-position
239        REAL(wp)     ::  y             !< y-position
240        REAL(wp)     ::  z             !< z-position
[2265]241        INTEGER(iwp) ::  class         !< radius class needed for collision
242        INTEGER(iwp) ::  group         !< number of particle group
[2305]243        INTEGER(idp) ::  id            !< particle ID (64 bit integer)
[2265]244        LOGICAL      ::  particle_mask !< if this parameter is set to false the particle will be deleted
245        INTEGER(iwp) ::  block_nr      !< number for sorting (removable?)
[1359]246    END TYPE particle_type
247
[2265]248    TYPE(particle_type), DIMENSION(:), POINTER ::  particles       !< Particle array for this grid cell
249    TYPE(particle_type)                        ::  zero_particle   !< zero particle to avoid weird thinge
[1359]250
251    TYPE particle_groups_type
252        SEQUENCE
[2265]253        REAL(wp) ::  density_ratio  !< density ratio of the fluid and the particles
254        REAL(wp) ::  radius         !< radius of particle
255        REAL(wp) ::  exp_arg        !< exponential term of particle inertia
256        REAL(wp) ::  exp_term       !< exponential term of particle inertia
[1359]257    END TYPE particle_groups_type
258
259    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::    &
260       particle_groups
261
262    TYPE  grid_particle_def
[2265]263        INTEGER(iwp), DIMENSION(0:7)               ::  start_index        !< start particle index for current block
264        INTEGER(iwp), DIMENSION(0:7)               ::  end_index          !< end particle index for current block
[2305]265        INTEGER(iwp)                               ::  id_counter         !< particle id counter
[2265]266        LOGICAL                                    ::  time_loop_done     !< timestep loop for particle advection
267        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles          !< Particle array for this grid cell
[1359]268    END TYPE grid_particle_def
269
270    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
271
[2265]272    TYPE block_offset_def          !<
273        INTEGER(iwp) ::  i_off     !<
274        INTEGER(iwp) ::  j_off     !<
275        INTEGER(iwp) ::  k_off     !<
[1359]276    END TYPE block_offset_def
277
278    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
279
280    SAVE
281
282
283END MODULE particle_attributes
Note: See TracBrowser for help on using the repository browser.