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

Last change on this file since 850 was 850, checked in by raasch, 13 years ago

last commit documented

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