source: palm/tags/release-5.0/SOURCE/lpm.f90 @ 3955

Last change on this file since 3955 was 2701, checked in by suehring, 6 years ago

changes from last commit documented

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