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

Last change on this file since 2182 was 2182, checked in by schwenkel, 7 years ago

Added parameters for simplified particle initialization

  • Property svn:keywords set to Id
File size: 8.9 KB
RevLine 
[1682]1!> @file mod_particle_attributes.f90
[2000]2!------------------------------------------------------------------------------!
[1359]3! This file is part of PALM.
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!
[2101]17! Copyright 1997-2017 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1359]19!
20! Current revisions:
21! ------------------
[2182]22! Added parameters for simplified particle initialization.
[1937]23!
[1360]24! Former revisions:
25! -----------------
26! $Id: mod_particle_attributes.f90 2182 2017-03-17 14:27:40Z schwenkel $
[1937]27!
[2123]28! 2122 2017-01-18 12:22:54Z hoffmann
29! Calculation of particle ID
30! Particle attribute dvrp_psize renamed to user: this attribute can be used by
31! by the user to store any variable
32!
[2001]33! 2000 2016-08-20 18:09:15Z knoop
34! Forced header and separation lines into 80 columns
35!
[1937]36! 1936 2016-06-13 13:37:44Z suehring
37! +deallocate_memory, step_dealloc
38!
[1930]39! 1929 2016-06-09 16:25:25Z suehring
40! -sgs_wfu_par, sgs_wfv_par, sgs_wfw_par
41! + sgs_wf_par
[1360]42!
[1872]43! 1871 2016-04-15 11:46:09Z hoffmann
44! Initialization of aerosols added.
45!
[1851]46! 1849 2016-04-08 11:33:18Z hoffmann
47! bfactor, mass_of_solute, molecular_weight_of_solute, molecular_weight_of_water,
48! vanthoff added from modules
49!
[1832]50! 1831 2016-04-07 13:15:51Z hoffmann
51! palm_kernel removed, curvature_solution_effects added
52!
[1823]53! 1822 2016-04-07 07:49:42Z hoffmann
54! +collision_algorithm, all_or_nothing, average_impact
55! Tails removed.
56!
[1728]57! 1727 2015-11-20 07:22:02Z knoop
58! Bugfix: Cause of syntax warning gfortran preprocessor removed
59!
[1683]60! 1682 2015-10-07 23:56:08Z knoop
61! Code annotations made doxygen readable
62!
[1576]63! 1575 2015-03-27 09:56:27Z raasch
64! +seed_follows_topography
65!
[1360]66! 1359 2014-04-11 17:15:14Z hoffmann
[1359]67! new module containing all particle related variables
68! -dt_sort_particles
69!
70! Description:
71! ------------
[1682]72!> Definition of variables used to compute particle transport
[1359]73!------------------------------------------------------------------------------!
[1682]74MODULE particle_attributes
75 
[1359]76
77    USE kinds
78
[1822]79    CHARACTER(LEN=15) ::  bc_par_lr = 'cyclic'                    !< left/right boundary condition
80    CHARACTER(LEN=15) ::  bc_par_ns = 'cyclic'                    !< north/south boundary condition
81    CHARACTER(LEN=15) ::  bc_par_b  = 'reflect'                   !< bottom boundary condition
82    CHARACTER(LEN=15) ::  bc_par_t  = 'absorb'                    !< top boundary condition
83    CHARACTER(LEN=15) ::  collision_algorithm = 'all_or_nothing'  !< collision algorithm
84    CHARACTER(LEN=15) ::  collision_kernel = 'none'               !< collision kernel
[1359]85
[1822]86    INTEGER(iwp) ::  deleted_particles = 0,                                    &
[1359]87                     dissipation_classes = 10, ibc_par_lr,                     &
88                     ibc_par_ns, ibc_par_b, ibc_par_t, iran_part = -1234567,   &
89                     maximum_number_of_particles = 0,                          &
90                     min_nr_particle = 50,                                     &
91                     mpi_particle_type,                                        &
92                     number_of_particles = 0,                                  &
[1822]93                     number_of_particle_groups = 1,                            &
94                     number_of_sublayers = 20,                                 &
[2182]95                     number_particles_per_gridbox = -1,                        &
[1359]96                     offset_ocean_nzt = 0,                                     &
97                     offset_ocean_nzt_m1 = 0, particles_per_point = 1,         &
98                     particle_file_count = 0, radius_classes = 20,             &
[1936]99                     sort_count = 0, step_dealloc = 100,                       &
[1822]100                     total_number_of_particles,                                &
[1359]101                     trlp_count_sum, trlp_count_recv_sum, trrp_count_sum,      &
102                     trrp_count_recv_sum, trsp_count_sum, trsp_count_recv_sum, &
103                     trnp_count_sum, trnp_count_recv_sum
104
105    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10
106
107    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count
108
[1822]109    LOGICAL ::  all_or_nothing = .FALSE., average_impact = .FALSE.,            &
[1831]110                curvature_solution_effects = .FALSE.,                          &
[1936]111                deallocate_memory = .TRUE.,                                    &
[1831]112                hall_kernel = .FALSE., particle_advection = .FALSE.,           &
113                random_start_position = .FALSE.,                               &
[1359]114                read_particles_from_restartfile = .TRUE.,                      &
[1575]115                seed_follows_topography = .FALSE.,                             &
[1359]116                uniform_particles = .TRUE., use_kernel_tables = .FALSE.,       &
[1822]117                use_sgs_for_particles = .FALSE., wang_kernel = .FALSE.,        &
118                write_particle_statistics = .FALSE.
[1359]119
120    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
121                vertical_particle_advection = .TRUE.
122
123    REAL(wp) ::  alloc_factor = 20.0_wp, c_0 = 3.0_wp,                         &
124                 dt_min_part = 0.0002_wp, dt_prel = 9999999.9_wp,              &
125                 dt_write_particle_data = 9999999.9_wp,                        &
[1822]126                 end_time_prel = 9999999.9_wp,                                 &
[1359]127                 initial_weighting_factor = 1.0_wp,                            &
[2182]128                 number_concentration     = -1.0_wp,                           &
[1359]129                 particle_advection_start = 0.0_wp,                            &
[1929]130                 sgs_wf_part, time_prel = 0.0_wp, time_sort_particles = 0.0_wp,&
[1359]131                 time_write_particle_data = 0.0_wp, z0_av_global
132
133    REAL(wp), DIMENSION(max_number_of_particle_groups) ::                      &
134                 density_ratio = 9999999.9_wp, pdx = 9999999.9_wp,             &
135                 pdy = 9999999.9_wp, pdz = 9999999.9_wp, psb = 9999999.9_wp,   &
136                 psl = 9999999.9_wp, psn = 9999999.9_wp, psr = 9999999.9_wp,   &
137                 pss = 9999999.9_wp, pst = 9999999.9_wp, radius = 9999999.9_wp
138
139    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0
140
141    TYPE particle_type
142        SEQUENCE
[2122]143        REAL(wp)     ::  radius, age, age_m, dt_sum, user, e_m,                &
[1359]144                         origin_x, origin_y, origin_z, rvar1, rvar2, rvar3,    &
145                         speed_x, speed_y, speed_z, weight_factor, x, y, z
[2122]146        INTEGER(iwp) ::  class, group, id1, id2
[1359]147        LOGICAL      ::  particle_mask
148        INTEGER(iwp) ::  block_nr
149    END TYPE particle_type
150
[1822]151    TYPE(particle_type), DIMENSION(:), POINTER ::  particles
152    TYPE(particle_type)                        ::  zero_particle
[1359]153
154    TYPE particle_groups_type
155        SEQUENCE
156        REAL(wp) ::  density_ratio, radius, exp_arg, exp_term
157    END TYPE particle_groups_type
158
159    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::    &
160       particle_groups
161
162    TYPE  grid_particle_def
163        INTEGER(iwp), DIMENSION(0:7)               ::  start_index
164        INTEGER(iwp), DIMENSION(0:7)               ::  end_index
[2122]165        INTEGER(iwp)                               ::  id_counter
[1359]166        LOGICAL                                    ::  time_loop_done
167        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles                !Particle array for this grid cell
168    END TYPE grid_particle_def
169
170    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
171
172    TYPE block_offset_def
173        INTEGER(iwp) ::  i_off
174        INTEGER(iwp) ::  j_off
175        INTEGER(iwp) ::  k_off
176    END TYPE block_offset_def
177
178    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
179
[1871]180!
181!-- Lagrangian cloud model constants (especially for steering aerosols)
182    REAL(wp) ::  molecular_weight_of_solute = 0.05844_wp    !< mol. m. NaCl (kg mol-1)
183    REAL(wp) ::  molecular_weight_of_water = 0.01801528_wp  !< mol. m. H2O (kg mol-1)
184    REAL(wp) ::  rho_s = 2165.0_wp                          !< density of NaCl (kg m-3)
185    REAL(wp) ::  vanthoff = 2.0_wp                          !< van't Hoff factor for NaCl
186
187    REAL(wp) ::  n1 = 100.0_wp, s1 = 2.0_wp, rm1 = 0.05E-6_wp, &
188                 n2 =   0.0_wp, s2 = 2.0_wp, rm2 = 0.05E-6_wp, &
189                 n3 =   0.0_wp, s3 = 2.0_wp, rm3 = 0.05E-6_wp
190
191    LOGICAL  ::  monodisperse_aerosols      = .FALSE.       !< initialize monodisperse aerosols
192    LOGICAL  ::  init_aerosol_probabilistic = .FALSE.       !< how to initialize aerosol spectra
193
[1359]194    SAVE
195
196
197END MODULE particle_attributes
198
Note: See TracBrowser for help on using the repository browser.