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

Last change on this file since 1416 was 1416, checked in by suehring, 10 years ago

Bugfixes concerning new particle structure

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