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

Last change on this file since 1856 was 1852, checked in by hoffmann, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 7.8 KB
Line 
1!> @file mod_particle_attributes.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014  Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! ------------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: mod_particle_attributes.f90 1852 2016-04-08 14:07:36Z maronga $
26!
27! 1849 2016-04-08 11:33:18Z hoffmann
28! bfactor, mass_of_solute, molecular_weight_of_solute, molecular_weight_of_water,
29! vanthoff added from modules
30!
31! 1831 2016-04-07 13:15:51Z hoffmann
32! palm_kernel removed, curvature_solution_effects added
33!
34! 1822 2016-04-07 07:49:42Z hoffmann
35! +collision_algorithm, all_or_nothing, average_impact
36! Tails removed.
37!
38! 1727 2015-11-20 07:22:02Z knoop
39! Bugfix: Cause of syntax warning gfortran preprocessor removed
40!
41! 1682 2015-10-07 23:56:08Z knoop
42! Code annotations made doxygen readable
43!
44! 1575 2015-03-27 09:56:27Z raasch
45! +seed_follows_topography
46!
47! 1359 2014-04-11 17:15:14Z hoffmann
48! new module containing all particle related variables
49! -dt_sort_particles
50!
51! Description:
52! ------------
53!> Definition of variables used to compute particle transport
54!------------------------------------------------------------------------------!
55MODULE particle_attributes
56 
57
58    USE kinds
59
60    CHARACTER(LEN=15) ::  bc_par_lr = 'cyclic'                    !< left/right boundary condition
61    CHARACTER(LEN=15) ::  bc_par_ns = 'cyclic'                    !< north/south boundary condition
62    CHARACTER(LEN=15) ::  bc_par_b  = 'reflect'                   !< bottom boundary condition
63    CHARACTER(LEN=15) ::  bc_par_t  = 'absorb'                    !< top boundary condition
64    CHARACTER(LEN=15) ::  collision_algorithm = 'all_or_nothing'  !< collision algorithm
65    CHARACTER(LEN=15) ::  collision_kernel = 'none'               !< collision kernel
66
67    INTEGER(iwp) ::  deleted_particles = 0,                                    &
68                     dissipation_classes = 10, ibc_par_lr,                     &
69                     ibc_par_ns, ibc_par_b, ibc_par_t, iran_part = -1234567,   &
70                     maximum_number_of_particles = 0,                          &
71                     min_nr_particle = 50,                                     &
72                     mpi_particle_type,                                        &
73                     number_of_particles = 0,                                  &
74                     number_of_particle_groups = 1,                            &
75                     number_of_sublayers = 20,                                 &
76                     offset_ocean_nzt = 0,                                     &
77                     offset_ocean_nzt_m1 = 0, particles_per_point = 1,         &
78                     particle_file_count = 0, radius_classes = 20,             &
79                     sort_count = 0,                                           &
80                     total_number_of_particles,                                &
81                     trlp_count_sum, trlp_count_recv_sum, trrp_count_sum,      &
82                     trrp_count_recv_sum, trsp_count_sum, trsp_count_recv_sum, &
83                     trnp_count_sum, trnp_count_recv_sum
84
85    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10
86
87    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count
88
89    LOGICAL ::  all_or_nothing = .FALSE., average_impact = .FALSE.,            &
90                curvature_solution_effects = .FALSE.,                          &
91                hall_kernel = .FALSE., particle_advection = .FALSE.,           &
92                random_start_position = .FALSE.,                               &
93                read_particles_from_restartfile = .TRUE.,                      &
94                seed_follows_topography = .FALSE.,                             &
95                uniform_particles = .TRUE., use_kernel_tables = .FALSE.,       &
96                use_sgs_for_particles = .FALSE., wang_kernel = .FALSE.,        &
97                write_particle_statistics = .FALSE.
98
99    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
100                vertical_particle_advection = .TRUE.
101
102    REAL(wp) ::  alloc_factor = 20.0_wp, c_0 = 3.0_wp,                         &
103                 dt_min_part = 0.0002_wp, dt_prel = 9999999.9_wp,              &
104                 dt_write_particle_data = 9999999.9_wp,                        &
105                 end_time_prel = 9999999.9_wp,                                 &
106                 initial_weighting_factor = 1.0_wp,                            &
107                 particle_advection_start = 0.0_wp,                            &
108                 sgs_wfu_part = 0.3333333_wp, sgs_wfv_part = 0.3333333_wp,     &
109                 sgs_wfw_part = 0.3333333_wp, time_prel = 0.0_wp,              &
110                 time_sort_particles = 0.0_wp,                                 &
111                 time_write_particle_data = 0.0_wp, z0_av_global
112
113    REAL(wp), DIMENSION(max_number_of_particle_groups) ::                      &
114                 density_ratio = 9999999.9_wp, pdx = 9999999.9_wp,             &
115                 pdy = 9999999.9_wp, pdz = 9999999.9_wp, psb = 9999999.9_wp,   &
116                 psl = 9999999.9_wp, psn = 9999999.9_wp, psr = 9999999.9_wp,   &
117                 pss = 9999999.9_wp, pst = 9999999.9_wp, radius = 9999999.9_wp
118
119    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0
120
121!
122!-- Lagrangian cloud model constants
123    REAL(wp) ::  mass_of_solute = 1.0E-17_wp                !< soluted NaCl (kg)
124    REAL(wp) ::  molecular_weight_of_solute = 0.05844_wp    !< mol. m. NaCl (kg mol-1)
125    REAL(wp) ::  molecular_weight_of_water = 0.01801528_wp  !< mol. m. H2O (kg mol-1)
126    REAL(wp) ::  vanthoff = 2.0_wp                          !< van't Hoff factor for NaCl
127
128    TYPE particle_type
129        SEQUENCE
130        REAL(wp)     ::  radius, age, age_m, dt_sum, dvrp_psize, e_m,          &
131                         origin_x, origin_y, origin_z, rvar1, rvar2, rvar3,    &
132                         speed_x, speed_y, speed_z, weight_factor, x, y, z
133        INTEGER(iwp) ::  class, group, tailpoints, tail_id
134        LOGICAL      ::  particle_mask
135        INTEGER(iwp) ::  block_nr
136    END TYPE particle_type
137
138    TYPE(particle_type), DIMENSION(:), POINTER ::  particles
139    TYPE(particle_type)                        ::  zero_particle
140
141    TYPE particle_groups_type
142        SEQUENCE
143        REAL(wp) ::  density_ratio, radius, exp_arg, exp_term
144    END TYPE particle_groups_type
145
146    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::    &
147       particle_groups
148
149    TYPE  grid_particle_def
150        INTEGER(iwp), DIMENSION(0:7)               ::  start_index
151        INTEGER(iwp), DIMENSION(0:7)               ::  end_index
152        LOGICAL                                    ::  time_loop_done
153        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles                !Particle array for this grid cell
154    END TYPE grid_particle_def
155
156    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
157
158    TYPE block_offset_def
159        INTEGER(iwp) ::  i_off
160        INTEGER(iwp) ::  j_off
161        INTEGER(iwp) ::  k_off
162    END TYPE block_offset_def
163
164    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
165
166    SAVE
167
168
169END MODULE particle_attributes
170
Note: See TracBrowser for help on using the repository browser.