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

Last change on this file since 1360 was 1360, checked in by hoffmann, 10 years ago

last commit documented

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