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

Last change on this file since 3655 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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