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

Last change on this file since 1032 was 852, checked in by raasch, 12 years ago

last commit documented

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