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

Last change on this file since 2259 was 2233, checked in by suehring, 7 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 15.1 KB
Line 
1!> @file lpm.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
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: lpm.f90 2233 2017-05-30 18:08:54Z gronemeier $
27!
28! 2232 2017-05-30 17:47:52Z suehring
29! Adjustments to new topography concept
30!
31! 2000 2016-08-20 18:09:15Z knoop
32! Forced header and separation lines into 80 columns
33!
34! 1936 2016-06-13 13:37:44Z suehring
35! Call routine for deallocation of unused memory.
36! Formatting adjustments
37!
38! 1929 2016-06-09 16:25:25Z suehring
39! Call wall boundary conditions only if particles are in the vertical range of
40! topography.
41!
42! 1822 2016-04-07 07:49:42Z hoffmann
43! Tails removed.
44!
45! Initialization of sgs model not necessary for the use of cloud_droplets and
46! use_sgs_for_particles.
47!
48! lpm_release_set integrated.
49!
50! Unused variabled removed.
51!
52! 1682 2015-10-07 23:56:08Z knoop
53! Code annotations made doxygen readable
54!
55! 1416 2014-06-04 16:04:03Z suehring
56! user_lpm_advec is called for each gridpoint.
57! Bugfix: in order to prevent an infinite loop, time_loop_done is set .TRUE.
58! at the head of the do-loop. 
59!
60! 1359 2014-04-11 17:15:14Z hoffmann
61! New particle structure integrated.
62! Kind definition added to all floating point numbers.
63!
64! 1320 2014-03-20 08:40:49Z raasch
65! ONLY-attribute added to USE-statements,
66! kind-parameters added to all INTEGER and REAL declaration statements,
67! kinds are defined in new module kinds,
68! revision history before 2012 removed,
69! comment fields (!:) to be used for variable explanations added to
70! all variable declaration statements
71!
72! 1318 2014-03-17 13:35:16Z raasch
73! module interfaces removed
74!
75! 1036 2012-10-22 13:43:42Z raasch
76! code put under GPL (PALM 3.9)
77!
78! 851 2012-03-15 14:32:58Z raasch
79! Bugfix: resetting of particle_mask and tail mask moved from routine
80! lpm_exchange_horiz to here (end of sub-timestep loop)
81!
82! 849 2012-03-15 10:35:09Z raasch
83! original routine advec_particles split into several subroutines and renamed
84! lpm
85!
86! 831 2012-02-22 00:29:39Z raasch
87! thermal_conductivity_l and diff_coeff_l now depend on temperature and
88! pressure
89!
90! 828 2012-02-21 12:00:36Z raasch
91! fast hall/wang kernels with fixed radius/dissipation classes added,
92! particle feature color renamed class, routine colker renamed
93! recalculate_kernel,
94! lower limit for droplet radius changed from 1E-7 to 1E-8
95!
96! Bugfix: transformation factor for dissipation changed from 1E5 to 1E4
97!
98! 825 2012-02-19 03:03:44Z raasch
99! droplet growth by condensation may include curvature and solution effects,
100! initialisation of temporary particle array for resorting removed,
101! particle attributes speed_x|y|z_sgs renamed rvar1|2|3,
102! module wang_kernel_mod renamed lpm_collision_kernels_mod,
103! wang_collision_kernel renamed wang_kernel
104!
105!
106! Revision 1.1  1999/11/25 16:16:06  raasch
107! Initial revision
108!
109!
110! Description:
111! ------------
112!> Particle advection
113!------------------------------------------------------------------------------!
114 SUBROUTINE lpm
115 
116
117    USE arrays_3d,                                                             &
118        ONLY:  ql_c, ql_v, ql_vp
119
120    USE control_parameters,                                                    &
121        ONLY:  cloud_droplets, dt_3d, dt_3d_reached, dt_3d_reached_l,          &
122               molecular_viscosity, simulated_time, topography
123
124    USE cpulog,                                                                &
125        ONLY:  cpu_log, log_point, log_point_s
126
127    USE indices,                                                               &
128        ONLY: nxl, nxr, nys, nyn, nzb, nzb_max, nzt
129
130    USE kinds
131
132    USE lpm_exchange_horiz_mod,                                                &
133        ONLY:  dealloc_particles_array, lpm_exchange_horiz, lpm_move_particle
134
135    USE lpm_init_mod,                                                          &
136        ONLY: lpm_create_particle, PHASE_RELEASE
137
138    USE lpm_pack_arrays_mod,                                                   &
139        ONLY:  lpm_pack_all_arrays
140
141    USE particle_attributes,                                                   &
142        ONLY:  collision_kernel, deleted_particles, deallocate_memory,         &
143               dt_write_particle_data, dt_prel, end_time_prel,                 &
144               grid_particles, number_of_particles, number_of_particle_groups, &
145               particles, particle_groups, prt_count, step_dealloc,            &
146               time_prel, time_write_particle_data, trlp_count_sum,            &
147               trlp_count_recv_sum, trnp_count_sum,                            &
148               trnp_count_recv_sum, trrp_count_sum, trrp_count_recv_sum,       &
149               trsp_count_sum, trsp_count_recv_sum,                            &
150               use_sgs_for_particles, write_particle_statistics
151
152    USE pegrid
153
154    IMPLICIT NONE
155
156    INTEGER(iwp)       ::  i                  !<
157    INTEGER(iwp)       ::  ie                 !<
158    INTEGER(iwp)       ::  is                 !<
159    INTEGER(iwp)       ::  j                  !<
160    INTEGER(iwp)       ::  je                 !<
161    INTEGER(iwp)       ::  js                 !<
162    INTEGER(iwp), SAVE ::  lpm_count = 0      !<
163    INTEGER(iwp)       ::  k                  !<
164    INTEGER(iwp)       ::  ke                 !<
165    INTEGER(iwp)       ::  ks                 !<
166    INTEGER(iwp)       ::  m                  !<
167    INTEGER(iwp), SAVE ::  steps = 0          !<
168
169    LOGICAL            ::  first_loop_stride  !<
170
171    CALL cpu_log( log_point(25), 'lpm', 'start' )
172
173!
174!-- Write particle data at current time on file.
175!-- This has to be done here, before particles are further processed,
176!-- because they may be deleted within this timestep (in case that
177!-- dt_write_particle_data = dt_prel = particle_maximum_age).
178    time_write_particle_data = time_write_particle_data + dt_3d
179    IF ( time_write_particle_data >= dt_write_particle_data )  THEN
180
181       CALL lpm_data_output_particles
182!
183!--    The MOD function allows for changes in the output interval with restart
184!--    runs.
185       time_write_particle_data = MOD( time_write_particle_data, &
186                                  MAX( dt_write_particle_data, dt_3d ) )
187    ENDIF
188
189!
190!-- Initialize arrays for marking those particles to be deleted after the
191!-- (sub-) timestep
192    deleted_particles = 0
193
194!
195!-- Initialize variables used for accumulating the number of particles
196!-- exchanged between the subdomains during all sub-timesteps (if sgs
197!-- velocities are included). These data are output further below on the
198!-- particle statistics file.
199    trlp_count_sum      = 0
200    trlp_count_recv_sum = 0
201    trrp_count_sum      = 0
202    trrp_count_recv_sum = 0
203    trsp_count_sum      = 0
204    trsp_count_recv_sum = 0
205    trnp_count_sum      = 0
206    trnp_count_recv_sum = 0
207
208
209!
210!-- Calculate exponential term used in case of particle inertia for each
211!-- of the particle groups
212    DO  m = 1, number_of_particle_groups
213       IF ( particle_groups(m)%density_ratio /= 0.0_wp )  THEN
214          particle_groups(m)%exp_arg  =                                        &
215                    4.5_wp * particle_groups(m)%density_ratio *                &
216                    molecular_viscosity / ( particle_groups(m)%radius )**2
217
218          particle_groups(m)%exp_term = EXP( -particle_groups(m)%exp_arg *     &
219                    dt_3d )
220       ENDIF
221    ENDDO
222
223!
224!-- If necessary, release new set of particles
225    IF ( time_prel >= dt_prel  .AND.  end_time_prel > simulated_time )  THEN
226
227       CALL lpm_create_particle(PHASE_RELEASE)
228!
229!--    The MOD function allows for changes in the output interval with
230!--    restart runs.
231       time_prel = MOD( time_prel, MAX( dt_prel, dt_3d ) )
232
233    ENDIF
234!
235!-- Reset summation arrays
236    IF ( cloud_droplets)  THEN
237       ql_c  = 0.0_wp
238       ql_v  = 0.0_wp
239       ql_vp = 0.0_wp
240    ENDIF
241
242    first_loop_stride = .TRUE.
243    grid_particles(:,:,:)%time_loop_done = .TRUE.
244!
245!-- Timestep loop for particle advection.
246!-- This loop has to be repeated until the advection time of every particle
247!-- (within the total domain!) has reached the LES timestep (dt_3d).
248!-- In case of including the SGS velocities, the particle timestep may be
249!-- smaller than the LES timestep (because of the Lagrangian timescale
250!-- restriction) and particles may require to undergo several particle
251!-- timesteps, before the LES timestep is reached. Because the number of these
252!-- particle timesteps to be carried out is unknown at first, these steps are
253!-- carried out in the following infinite loop with exit condition.
254    DO
255       CALL cpu_log( log_point_s(44), 'lpm_advec', 'start' )
256       CALL cpu_log( log_point_s(44), 'lpm_advec', 'pause' )
257       
258       grid_particles(:,:,:)%time_loop_done = .TRUE.
259!
260!--    If particle advection includes SGS velocity components, calculate the
261!--    required SGS quantities (i.e. gradients of the TKE, as well as
262!--    horizontally averaged profiles of the SGS TKE and the resolved-scale
263!--    velocity variances)
264
265       IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets )  THEN
266          CALL lpm_init_sgs_tke
267       ENDIF
268
269       DO  i = nxl, nxr
270          DO  j = nys, nyn
271             DO  k = nzb+1, nzt
272
273                number_of_particles = prt_count(k,j,i)
274!
275!--             If grid cell gets empty, flag must be true
276                IF ( number_of_particles <= 0 )  THEN
277                   grid_particles(k,j,i)%time_loop_done = .TRUE.
278                   CYCLE
279                ENDIF
280
281                IF ( .NOT. first_loop_stride  .AND.  &
282                     grid_particles(k,j,i)%time_loop_done ) CYCLE
283
284                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
285
286                particles(1:number_of_particles)%particle_mask = .TRUE.
287!
288!--             Initialize the variable storing the total time that a particle
289!--             has advanced within the timestep procedure
290                IF ( first_loop_stride )  THEN
291                   particles(1:number_of_particles)%dt_sum = 0.0_wp
292                ENDIF
293!
294!--             Particle (droplet) growth by condensation/evaporation and
295!--             collision
296                IF ( cloud_droplets  .AND.  first_loop_stride)  THEN
297!
298!--                Droplet growth by condensation / evaporation
299                   CALL lpm_droplet_condensation(i,j,k)
300!
301!--                Particle growth by collision
302                   IF ( collision_kernel /= 'none' )  THEN
303                      CALL lpm_droplet_collision(i,j,k)
304                   ENDIF
305
306                ENDIF
307!
308!--             Initialize the switch used for the loop exit condition checked
309!--             at the end of this loop. If at least one particle has failed to
310!--             reach the LES timestep, this switch will be set false in
311!--             lpm_advec.
312                dt_3d_reached_l = .TRUE.
313
314!
315!--             Particle advection
316                CALL lpm_advec(i,j,k)
317!
318!--             Particle reflection from walls. Only applied if the particles
319!--             are in the vertical range of the topography. (Here, some
320!--             optimization is still possible.)
321                IF ( topography /= 'flat' .AND. k < nzb_max + 2 )  THEN
322                   CALL lpm_boundary_conds( 'walls' )
323                ENDIF
324!
325!--             User-defined actions after the calculation of the new particle
326!--             position
327                CALL user_lpm_advec(i,j,k)
328!
329!--             Apply boundary conditions to those particles that have crossed
330!--             the top or bottom boundary and delete those particles, which are
331!--             older than allowed
332                CALL lpm_boundary_conds( 'bottom/top' )
333!
334!---            If not all particles of the actual grid cell have reached the
335!--             LES timestep, this cell has to to another loop iteration. Due to
336!--             the fact that particles can move into neighboring grid cell,
337!--             these neighbor cells also have to perform another loop iteration
338                IF ( .NOT. dt_3d_reached_l )  THEN
339                   ks = MAX(nzb+1,k)
340                   ke = MIN(nzt,k)
341                   js = MAX(nys,j)
342                   je = MIN(nyn,j)
343                   is = MAX(nxl,i)
344                   ie = MIN(nxr,i)
345                   grid_particles(ks:ke,js:je,is:ie)%time_loop_done = .FALSE.
346                ENDIF
347
348             ENDDO
349          ENDDO
350       ENDDO
351
352       steps = steps + 1
353       dt_3d_reached_l = ALL(grid_particles(:,:,:)%time_loop_done)
354!
355!--    Find out, if all particles on every PE have completed the LES timestep
356!--    and set the switch corespondingly
357#if defined( __parallel )
358       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
359       CALL MPI_ALLREDUCE( dt_3d_reached_l, dt_3d_reached, 1, MPI_LOGICAL, &
360                           MPI_LAND, comm2d, ierr )
361#else
362       dt_3d_reached = dt_3d_reached_l
363#endif
364
365       CALL cpu_log( log_point_s(44), 'lpm_advec', 'stop' )
366
367!
368!--    Increment time since last release
369       IF ( dt_3d_reached )  time_prel = time_prel + dt_3d
370!
371!--    Move Particles local to PE to a different grid cell
372       CALL lpm_move_particle
373
374!
375!--    Horizontal boundary conditions including exchange between subdmains
376       CALL lpm_exchange_horiz
377!
378!--    Pack particles (eliminate those marked for deletion),
379!--    determine new number of particles
380       CALL lpm_pack_all_arrays
381
382!
383!--    Initialize variables for the next (sub-) timestep, i.e., for marking
384!--    those particles to be deleted after the timestep
385       deleted_particles = 0
386
387       IF ( dt_3d_reached )  EXIT
388
389       first_loop_stride = .FALSE.
390    ENDDO   ! timestep loop
391
392!
393!-- Calculate the new liquid water content for each grid box
394    IF ( cloud_droplets )  CALL lpm_calc_liquid_water_content
395!
396!-- Deallocate unused memory
397    IF ( deallocate_memory  .AND.  lpm_count == step_dealloc )  THEN
398       CALL dealloc_particles_array
399       lpm_count = 0
400    ELSEIF ( deallocate_memory )  THEN
401       lpm_count = lpm_count + 1
402    ENDIF
403
404!
405!-- Set particle attributes.
406!-- Feature is not available if collision is activated, because the respective
407!-- particle attribute (class) is then used for storing the particle radius
408!-- class.
409    IF ( collision_kernel == 'none' )  CALL lpm_set_attributes
410
411!
412!-- Set particle attributes defined by the user
413    CALL user_lpm_set_attributes
414
415!
416!-- Write particle statistics (in particular the number of particles
417!-- exchanged between the subdomains) on file
418    IF ( write_particle_statistics )  CALL lpm_write_exchange_statistics
419
420    CALL cpu_log( log_point(25), 'lpm', 'stop' )
421
422 END SUBROUTINE lpm
Note: See TracBrowser for help on using the repository browser.