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

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

Bugfix: resetting of particle_mask and tail mask moved from routine lpm_exchange_horiz to routine lpm (end of sub-timestep loop)

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