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

Last change on this file since 1930 was 1930, checked in by suehring, 8 years ago

last commit documented

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