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

Last change on this file since 4017 was 4017, checked in by schwenkel, 5 years ago

Modularization of all lagrangian particle model code components

  • Property svn:keywords set to Id
File size: 8.9 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!
[3655]17! Copyright 1997-2019 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 4017 2019-06-06 12:16:46Z schwenkel $
[3786]27! interoperable C datatypes introduced in particle type to avoid compiler warnings
28!
29! 3720 2019-02-06 13:19:55Z knoop
[3560]30! time_prel replaced by last_particle_release_time
31!
32! 3405 2018-10-23 15:34:41Z raasch
[3405]33! bugfix: BIND attribute added to derived type particle_type
34!
35! 2718 2018-01-02 08:49:38Z maronga
[2716]36! Corrected "Former revisions" section
37!
38! 2696 2017-12-14 17:12:51Z kanani
39! Change in file header (GPL part)
40!
41! 2375 2017-08-29 14:10:28Z schwenkel
[2375]42! molecular_weight_of_solute, molecular_weight_of_water, vanthoff removed and
43! added in modules. Parameters are also used in bulk-microphysics.
44!
45! 2312 2017-07-14 20:26:51Z hoffmann
[2312]46! Aerosol initialization improved.
47!
48! 2305 2017-07-06 11:18:47Z hoffmann
[2305]49! Improved calculation of particle IDs.
[2312]50!
[2305]51! 2278 2017-06-12 13:08:18Z schwenkel
[2278]52! Added comments
[2312]53!
[2278]54! 2265 2017-06-08 16:58:28Z schwenkel
[2265]55! Unused variables removed.
[2312]56!
[2265]57! 2263 2017-06-08 14:59:01Z schwenkel
[2263]58! Implemented splitting and merging algorithm
[2312]59!
[2263]60! 2183 2017-03-17 14:29:15Z schwenkel
[1937]61!
[2183]62! 2182 2017-03-17 14:27:40Z schwenkel
63! Added parameters for simplified particle initialization.
[2312]64!
[2123]65! 2122 2017-01-18 12:22:54Z hoffmann
66! Calculation of particle ID
67! Particle attribute dvrp_psize renamed to user: this attribute can be used by
68! by the user to store any variable
69!
[2001]70! 2000 2016-08-20 18:09:15Z knoop
71! Forced header and separation lines into 80 columns
[2312]72!
[1937]73! 1936 2016-06-13 13:37:44Z suehring
74! +deallocate_memory, step_dealloc
75!
[1930]76! 1929 2016-06-09 16:25:25Z suehring
77! -sgs_wfu_par, sgs_wfv_par, sgs_wfw_par
78! + sgs_wf_par
[1360]79!
[1872]80! 1871 2016-04-15 11:46:09Z hoffmann
81! Initialization of aerosols added.
82!
[1851]83! 1849 2016-04-08 11:33:18Z hoffmann
84! bfactor, mass_of_solute, molecular_weight_of_solute, molecular_weight_of_water,
85! vanthoff added from modules
86!
[1832]87! 1831 2016-04-07 13:15:51Z hoffmann
88! palm_kernel removed, curvature_solution_effects added
89!
[1823]90! 1822 2016-04-07 07:49:42Z hoffmann
91! +collision_algorithm, all_or_nothing, average_impact
92! Tails removed.
93!
[1728]94! 1727 2015-11-20 07:22:02Z knoop
[2312]95! Bugfix: Cause of syntax warning gfortran preprocessor removed
96!
[1683]97! 1682 2015-10-07 23:56:08Z knoop
[2312]98! Code annotations made doxygen readable
[1683]99!
[1576]100! 1575 2015-03-27 09:56:27Z raasch
101! +seed_follows_topography
102!
[1360]103! 1359 2014-04-11 17:15:14Z hoffmann
[1359]104! new module containing all particle related variables
105! -dt_sort_particles
106!
107! Description:
108! ------------
[1682]109!> Definition of variables used to compute particle transport
[1359]110!------------------------------------------------------------------------------!
[1682]111MODULE particle_attributes
[1359]112
[3405]113    USE, INTRINSIC ::  ISO_C_BINDING
[2312]114
[1359]115    USE kinds
116
[2265]117    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
[2263]118    INTEGER(iwp) ::  ibc_par_b                                    !< particle bottom boundary condition dummy
119    INTEGER(iwp) ::  ibc_par_lr                                   !< particle left/right boundary condition dummy
120    INTEGER(iwp) ::  ibc_par_ns                                   !< particle north/south boundary condition dummy
121    INTEGER(iwp) ::  ibc_par_t                                    !< particle top boundary condition dummy
[2312]122    INTEGER(iwp) ::  min_nr_particle = 50                         !< namelist parameter (see documentation)
123    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)
124    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
[1359]125
[2263]126    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
[1359]127
[2263]128    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
[4017]129   
[2263]130    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
[4017]131    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)   
[2263]132    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
[2312]133
[2265]134    REAL(wp) ::  alloc_factor = 20.0_wp                    !< namelist parameter (see documentation)
135    REAL(wp) ::  particle_advection_start = 0.0_wp         !< namelist parameter (see documentation)
[1359]136
[3786]137!
138!-- WARNING: For compatibility of derived types, the BIND attribute is required, and interoperable C
139!-- datatypes must be used. These type are hard wired here! So changes in working precision (wp, iwp)
140!-- will not affect the particle_type!
141!-- The main reason for introducing the interoperable datatypes was to avoid compiler warnings of
142!-- the gfortran compiler.
143!-- The BIND attribite is required because of C_F_POINTER usage in the pmc particle interface.
[3405]144    TYPE, BIND(C) ::  particle_type
[3786]145        REAL(C_DOUBLE) ::  aux1          !< auxiliary multi-purpose feature
146        REAL(C_DOUBLE) ::  aux2          !< auxiliary multi-purpose feature
147        REAL(C_DOUBLE) ::  radius        !< radius of particle
148        REAL(C_DOUBLE) ::  age           !< age of particle
149        REAL(C_DOUBLE) ::  age_m         !<
150        REAL(C_DOUBLE) ::  dt_sum        !<
151        REAL(C_DOUBLE) ::  e_m           !< interpolated sgs tke
152        REAL(C_DOUBLE) ::  origin_x      !< origin x-position of particle (changed cyclic bc)
153        REAL(C_DOUBLE) ::  origin_y      !< origin y-position of particle (changed cyclic bc)
154        REAL(C_DOUBLE) ::  origin_z      !< origin z-position of particle (changed cyclic bc)
155        REAL(C_DOUBLE) ::  rvar1         !<
156        REAL(C_DOUBLE) ::  rvar2         !<
157        REAL(C_DOUBLE) ::  rvar3         !<
158        REAL(C_DOUBLE) ::  speed_x       !< speed of particle in x
159        REAL(C_DOUBLE) ::  speed_y       !< speed of particle in y
160        REAL(C_DOUBLE) ::  speed_z       !< speed of particle in z
161        REAL(C_DOUBLE) ::  weight_factor !< weighting factor
162        REAL(C_DOUBLE) ::  x             !< x-position
163        REAL(C_DOUBLE) ::  y             !< y-position
164        REAL(C_DOUBLE) ::  z             !< z-position
165        INTEGER(C_INT) ::  class         !< radius class needed for collision
166        INTEGER(C_INT) ::  group         !< number of particle group
167        INTEGER(C_LONG_LONG) ::  id            !< particle ID (64 bit integer)
[3720]168        LOGICAL(C_BOOL) ::  particle_mask !< if this parameter is set to false the particle will be deleted
[3786]169        INTEGER(C_INT) ::  block_nr      !< number for sorting (removable?)
[1359]170    END TYPE particle_type
171
[2265]172    TYPE(particle_type), DIMENSION(:), POINTER ::  particles       !< Particle array for this grid cell
173    TYPE(particle_type)                        ::  zero_particle   !< zero particle to avoid weird thinge
[1359]174
175    TYPE particle_groups_type
176        SEQUENCE
[2265]177        REAL(wp) ::  density_ratio  !< density ratio of the fluid and the particles
178        REAL(wp) ::  radius         !< radius of particle
179        REAL(wp) ::  exp_arg        !< exponential term of particle inertia
180        REAL(wp) ::  exp_term       !< exponential term of particle inertia
[1359]181    END TYPE particle_groups_type
182
183    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::    &
184       particle_groups
185
186    TYPE  grid_particle_def
[2265]187        INTEGER(iwp), DIMENSION(0:7)               ::  start_index        !< start particle index for current block
188        INTEGER(iwp), DIMENSION(0:7)               ::  end_index          !< end particle index for current block
[2305]189        INTEGER(iwp)                               ::  id_counter         !< particle id counter
[2265]190        LOGICAL                                    ::  time_loop_done     !< timestep loop for particle advection
191        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles          !< Particle array for this grid cell
[1359]192    END TYPE grid_particle_def
193
194    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
195
[2265]196    TYPE block_offset_def          !<
197        INTEGER(iwp) ::  i_off     !<
198        INTEGER(iwp) ::  j_off     !<
199        INTEGER(iwp) ::  k_off     !<
[1359]200    END TYPE block_offset_def
201
202    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
203
204    SAVE
205
206
207END MODULE particle_attributes
Note: See TracBrowser for help on using the repository browser.