source: palm/trunk/SOURCE/lpm.f90 @ 1321

Last change on this file since 1321 was 1321, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 10.9 KB
Line 
1 SUBROUTINE lpm
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
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!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: lpm.f90 1321 2014-03-20 09:40:40Z raasch $
27!
28! 1320 2014-03-20 08:40:49Z raasch
29! ONLY-attribute added to USE-statements,
30! kind-parameters added to all INTEGER and REAL declaration statements,
31! kinds are defined in new module kinds,
32! revision history before 2012 removed,
33! comment fields (!:) to be used for variable explanations added to
34! all variable declaration statements
35!
36! 1318 2014-03-17 13:35:16Z raasch
37! module interfaces removed
38!
39! 1036 2012-10-22 13:43:42Z raasch
40! code put under GPL (PALM 3.9)
41!
42! 851 2012-03-15 14:32:58Z raasch
43! Bugfix: resetting of particle_mask and tail mask moved from routine
44! lpm_exchange_horiz to here (end of sub-timestep loop)
45!
46! 849 2012-03-15 10:35:09Z raasch
47! original routine advec_particles split into several subroutines and renamed
48! lpm
49!
50! 831 2012-02-22 00:29:39Z raasch
51! thermal_conductivity_l and diff_coeff_l now depend on temperature and
52! pressure
53!
54! 828 2012-02-21 12:00:36Z raasch
55! fast hall/wang kernels with fixed radius/dissipation classes added,
56! particle feature color renamed class, routine colker renamed
57! recalculate_kernel,
58! lower limit for droplet radius changed from 1E-7 to 1E-8
59!
60! Bugfix: transformation factor for dissipation changed from 1E5 to 1E4
61!
62! 825 2012-02-19 03:03:44Z raasch
63! droplet growth by condensation may include curvature and solution effects,
64! initialisation of temporary particle array for resorting removed,
65! particle attributes speed_x|y|z_sgs renamed rvar1|2|3,
66! module wang_kernel_mod renamed lpm_collision_kernels_mod,
67! wang_collision_kernel renamed wang_kernel
68!
69!
70! Revision 1.1  1999/11/25 16:16:06  raasch
71! Initial revision
72!
73!
74! Description:
75! ------------
76! Particle advection
77!------------------------------------------------------------------------------!
78
79    USE arrays_3d,                                                             &
80        ONLY:  ql_c, ql_v, ql_vp
81
82    USE control_parameters,                                                    &
83        ONLY:  cloud_droplets, dt_3d, dt_3d_reached, dt_3d_reached_l,          &
84               molecular_viscosity, simulated_time
85
86    USE cpulog,                                                                &
87        ONLY:  cpu_log, log_point, log_point_s
88
89    USE kinds
90
91    USE particle_attributes,                                                   &
92        ONLY:  collision_kernel, deleted_particles, dt_sort_particles,         &
93               deleted_tails, dt_write_particle_data, dt_prel, end_time_prel,  &
94               number_of_particles, number_of_particle_groups,particles,       &
95               particle_groups, particle_mask, trlp_count_sum, tail_mask,      &
96               time_prel, time_sort_particles, time_write_particle_data,       &
97               trlp_count_recv_sum, trnp_count_sum, trnp_count_recv_sum,       &
98               trrp_count_sum, trrp_count_recv_sum, trsp_count_sum,            &
99               trsp_count_recv_sum, use_particle_tails, use_sgs_for_particles, &
100               write_particle_statistics
101
102    USE pegrid
103
104    IMPLICIT NONE
105
106    INTEGER(iwp) ::  m                       !:
107
108
109    CALL cpu_log( log_point(25), 'lpm', 'start' )
110
111!
112!-- Write particle data at current time on file.
113!-- This has to be done here, before particles are further processed,
114!-- because they may be deleted within this timestep (in case that
115!-- dt_write_particle_data = dt_prel = particle_maximum_age).
116    time_write_particle_data = time_write_particle_data + dt_3d
117    IF ( time_write_particle_data >= dt_write_particle_data )  THEN
118
119       CALL lpm_data_output_particles
120!
121!--    The MOD function allows for changes in the output interval with restart
122!--    runs.
123       time_write_particle_data = MOD( time_write_particle_data, &
124                                  MAX( dt_write_particle_data, dt_3d ) )
125    ENDIF
126
127
128!
129!-- Initialize arrays for marking those particles/tails to be deleted after the
130!-- (sub-) timestep
131    particle_mask     = .TRUE.
132    deleted_particles = 0
133
134    IF ( use_particle_tails )  THEN
135       tail_mask = .TRUE.
136    ENDIF
137    deleted_tails = 0
138
139
140!
141!-- Initialize variables used for accumulating the number of particles
142!-- exchanged between the subdomains during all sub-timesteps (if sgs
143!-- velocities are included). These data are output further below on the
144!-- particle statistics file.
145    trlp_count_sum      = 0
146    trlp_count_recv_sum = 0
147    trrp_count_sum      = 0
148    trrp_count_recv_sum = 0
149    trsp_count_sum      = 0
150    trsp_count_recv_sum = 0
151    trnp_count_sum      = 0
152    trnp_count_recv_sum = 0
153
154
155!
156!-- Calculate exponential term used in case of particle inertia for each
157!-- of the particle groups
158    DO  m = 1, number_of_particle_groups
159       IF ( particle_groups(m)%density_ratio /= 0.0 )  THEN
160          particle_groups(m)%exp_arg  =                                        &
161                    4.5 * particle_groups(m)%density_ratio *                   &
162                    molecular_viscosity / ( particle_groups(m)%radius )**2
163          particle_groups(m)%exp_term = EXP( -particle_groups(m)%exp_arg * &
164                                             dt_3d )
165       ENDIF
166    ENDDO
167
168
169!
170!-- Particle (droplet) growth by condensation/evaporation and collision
171    IF ( cloud_droplets )  THEN
172
173!
174!--    Reset summation arrays
175       ql_c = 0.0;  ql_v = 0.0;  ql_vp = 0.0
176
177!
178!--    Droplet growth by condensation / evaporation
179       CALL lpm_droplet_condensation
180
181!
182!--    Particle growth by collision
183       IF ( collision_kernel /= 'none' )  CALL lpm_droplet_collision
184
185    ENDIF
186
187
188!
189!-- If particle advection includes SGS velocity components, calculate the
190!-- required SGS quantities (i.e. gradients of the TKE, as well as horizontally
191!-- averaged profiles of the SGS TKE and the resolved-scale velocity variances)
192    IF ( use_sgs_for_particles )  CALL lpm_init_sgs_tke
193
194
195!
196!-- Initialize the variable storing the total time that a particle has advanced
197!-- within the timestep procedure
198    particles(1:number_of_particles)%dt_sum = 0.0
199
200
201!
202!-- Timestep loop for particle advection.
203!-- This loop has to be repeated until the advection time of every particle
204!-- (within the total domain!) has reached the LES timestep (dt_3d).
205!-- In case of including the SGS velocities, the particle timestep may be
206!-- smaller than the LES timestep (because of the Lagrangian timescale restric-
207!-- tion) and particles may require to undergo several particle timesteps,
208!-- before the LES timestep is reached. Because the number of these particle
209!-- timesteps to be carried out is unknown at first, these steps are carried
210!-- out in the following infinite loop with exit condition.
211    DO
212
213       CALL cpu_log( log_point_s(44), 'lpm_advec', 'start' )
214
215!
216!--    Initialize the switch used for the loop exit condition checked at the
217!--    end of this loop.
218!--    If at least one particle has failed to reach the LES timestep, this
219!--    switch will be set false.
220       dt_3d_reached_l = .TRUE.
221
222!
223!--    Particle advection
224       CALL lpm_advec
225
226!
227!--    Particle reflection from walls
228       CALL lpm_boundary_conds( 'walls' )
229
230!
231!--    User-defined actions after the calculation of the new particle position
232       CALL user_lpm_advec
233
234!
235!--    Find out, if all particles on every PE have completed the LES timestep
236!--    and set the switch corespondingly
237#if defined( __parallel )
238       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
239       CALL MPI_ALLREDUCE( dt_3d_reached_l, dt_3d_reached, 1, MPI_LOGICAL, &
240                           MPI_LAND, comm2d, ierr )
241#else
242       dt_3d_reached = dt_3d_reached_l
243#endif
244
245       CALL cpu_log( log_point_s(44), 'lpm_advec', 'stop' )
246
247!
248!--    Increment time since last release
249       IF ( dt_3d_reached )  time_prel = time_prel + dt_3d
250
251!
252!--    If necessary, release new set of particles
253       IF ( time_prel >= dt_prel  .AND.  end_time_prel > simulated_time  .AND. &
254            dt_3d_reached )  THEN
255
256          CALL lpm_release_set
257
258!
259!--       The MOD function allows for changes in the output interval with
260!--       restart runs.
261          time_prel = MOD( time_prel, MAX( dt_prel, dt_3d ) )
262
263       ENDIF
264
265!
266!--    Horizontal boundary conditions including exchange between subdmains
267       CALL lpm_exchange_horiz
268
269!
270!--    Apply boundary conditions to those particles that have crossed the top or
271!--    bottom boundary and delete those particles, which are older than allowed
272       CALL lpm_boundary_conds( 'bottom/top' )
273
274!
275!--    Pack particles (eliminate those marked for deletion),
276!--    determine new number of particles
277       IF ( number_of_particles > 0  .AND.  deleted_particles > 0 )  THEN
278          CALL lpm_pack_arrays
279       ENDIF
280
281!
282!--    Initialize variables for the next (sub-) timestep, i.e. for marking those
283!--    particles to be deleted after the timestep
284       particle_mask     = .TRUE.
285       deleted_particles = 0
286
287       IF ( use_particle_tails )  THEN
288          tail_mask     = .TRUE.
289       ENDIF
290       deleted_tails = 0
291
292
293       IF ( dt_3d_reached )  EXIT
294
295    ENDDO   ! timestep loop
296
297
298!
299!-- Sort particles in the sequence the gridboxes are stored in the memory
300    time_sort_particles = time_sort_particles + dt_3d
301    IF ( time_sort_particles >= dt_sort_particles )  THEN
302       CALL lpm_sort_arrays
303       time_sort_particles = MOD( time_sort_particles, &
304                                  MAX( dt_sort_particles, dt_3d ) )
305    ENDIF
306
307
308!
309!-- Calculate the new liquid water content for each grid box
310    IF ( cloud_droplets )  CALL lpm_calc_liquid_water_content
311
312
313!
314!-- Set particle attributes.
315!-- Feature is not available if collision is activated, because the respective
316!-- particle attribute (class) is then used for storing the particle radius
317!-- class.
318    IF ( collision_kernel == 'none' )  CALL lpm_set_attributes
319
320
321!
322!-- Set particle attributes defined by the user
323    CALL user_lpm_set_attributes
324
325
326!
327!-- If required, add the current particle positions to the particle tails
328    IF ( use_particle_tails )  CALL lpm_extend_tails
329
330
331!
332!-- Write particle statistics (in particular the number of particles
333!-- exchanged between the subdomains) on file
334    IF ( write_particle_statistics )  CALL lpm_write_exchange_statistics
335
336    CALL cpu_log( log_point(25), 'lpm', 'stop' )
337
338
339 END SUBROUTINE lpm
Note: See TracBrowser for help on using the repository browser.