source: palm/trunk/SOURCE/lagrangian_particle_model_mod.f90 @ 4121

Last change on this file since 4121 was 4121, checked in by schwenkel, 6 years ago

Implementation of an simple method for interpolating the velocities to particle position

  • Property svn:keywords set to Id
File size: 350.1 KB
Line 
1!> @file lagrangian_particle_model_mod.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-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: lagrangian_particle_model_mod.f90 4121 2019-07-26 10:01:22Z schwenkel $
27! Implementation of an simple method for interpolating the velocities to
28! particle position
29!
30! 4114 2019-07-23 14:09:27Z schwenkel
31! Bugfix: Added working precision for if statement
32!
33! 4054 2019-06-27 07:42:18Z raasch
34! bugfix for calculating the minimum particle time step
35!
36! 4044 2019-06-19 12:28:27Z schwenkel
37! Bugfix in case of grid strecting: corrected calculation of k-Index
38!
39! 4043 2019-06-18 16:59:00Z schwenkel
40! Remove min_nr_particle, Add lpm_droplet_interactions_ptq into module
41!
42! 4028 2019-06-13 12:21:37Z schwenkel
43! Further modularization of particle code components
44!
45! 4020 2019-06-06 14:57:48Z schwenkel
46! Removing submodules
47!
48! 4018 2019-06-06 13:41:50Z eckhard
49! Bugfix for former revision
50!
51! 4017 2019-06-06 12:16:46Z schwenkel
52! Modularization of all lagrangian particle model code components
53!
54! 3655 2019-01-07 16:51:22Z knoop
55! bugfix to guarantee correct particle releases in case that the release
56! interval is smaller than the model timestep
57!
58! 2801 2018-02-14 16:01:55Z thiele
59! Changed lpm from subroutine to module.
60! Introduce particle transfer in nested models.
61!
62! 2718 2018-01-02 08:49:38Z maronga
63! Corrected "Former revisions" section
64!
65! 2701 2017-12-15 15:40:50Z suehring
66! Changes from last commit documented
67!
68! 2698 2017-12-14 18:46:24Z suehring
69! Grid indices passed to lpm_boundary_conds. (responsible Philipp Thiele)
70!
71! 2696 2017-12-14 17:12:51Z kanani
72! Change in file header (GPL part)
73!
74! 2606 2017-11-10 10:36:31Z schwenkel
75! Changed particle box locations: center of particle box now coincides
76! with scalar grid point of same index.
77! Renamed module and subroutines: lpm_pack_arrays_mod -> lpm_pack_and_sort_mod
78! lpm_pack_all_arrays -> lpm_sort_and_delete, lpm_pack_arrays -> lpm_pack
79! lpm_sort -> lpm_sort_timeloop_done
80!
81! 2418 2017-09-06 15:24:24Z suehring
82! Major bugfixes in modeling SGS particle speeds (since revision 1359).
83! Particle sorting added to distinguish between already completed and
84! non-completed particles.
85!
86! 2263 2017-06-08 14:59:01Z schwenkel
87! Implemented splitting and merging algorithm
88!
89! 2233 2017-05-30 18:08:54Z suehring
90!
91! 2232 2017-05-30 17:47:52Z suehring
92! Adjustments to new topography concept
93!
94! 2000 2016-08-20 18:09:15Z knoop
95! Forced header and separation lines into 80 columns
96!
97! 1936 2016-06-13 13:37:44Z suehring
98! Call routine for deallocation of unused memory.
99! Formatting adjustments
100!
101! 1929 2016-06-09 16:25:25Z suehring
102! Call wall boundary conditions only if particles are in the vertical range of
103! topography.
104!
105! 1822 2016-04-07 07:49:42Z hoffmann
106! Tails removed.
107!
108! Initialization of sgs model not necessary for the use of cloud_droplets and
109! use_sgs_for_particles.
110!
111! lpm_release_set integrated.
112!
113! Unused variabled removed.
114!
115! 1682 2015-10-07 23:56:08Z knoop
116! Code annotations made doxygen readable
117!
118! 1416 2014-06-04 16:04:03Z suehring
119! user_lpm_advec is called for each gridpoint.
120! Bugfix: in order to prevent an infinite loop, time_loop_done is set .TRUE.
121! at the head of the do-loop. 
122!
123! 1359 2014-04-11 17:15:14Z hoffmann
124! New particle structure integrated.
125! Kind definition added to all floating point numbers.
126!
127! 1320 2014-03-20 08:40:49Z raasch
128! ONLY-attribute added to USE-statements,
129! kind-parameters added to all INTEGER and REAL declaration statements,
130! kinds are defined in new module kinds,
131! revision history before 2012 removed,
132! comment fields (!:) to be used for variable explanations added to
133! all variable declaration statements
134!
135! 1318 2014-03-17 13:35:16Z raasch
136! module interfaces removed
137!
138! 1036 2012-10-22 13:43:42Z raasch
139! code put under GPL (PALM 3.9)
140!
141! 851 2012-03-15 14:32:58Z raasch
142! Bugfix: resetting of particle_mask and tail mask moved from routine
143! lpm_exchange_horiz to here (end of sub-timestep loop)
144!
145! 849 2012-03-15 10:35:09Z raasch
146! original routine advec_particles split into several subroutines and renamed
147! lpm
148!
149! 831 2012-02-22 00:29:39Z raasch
150! thermal_conductivity_l and diff_coeff_l now depend on temperature and
151! pressure
152!
153! 828 2012-02-21 12:00:36Z raasch
154! fast hall/wang kernels with fixed radius/dissipation classes added,
155! particle feature color renamed class, routine colker renamed
156! recalculate_kernel,
157! lower limit for droplet radius changed from 1E-7 to 1E-8
158!
159! Bugfix: transformation factor for dissipation changed from 1E5 to 1E4
160!
161! 825 2012-02-19 03:03:44Z raasch
162! droplet growth by condensation may include curvature and solution effects,
163! initialisation of temporary particle array for resorting removed,
164! particle attributes speed_x|y|z_sgs renamed rvar1|2|3,
165! module wang_kernel_mod renamed lpm_collision_kernels_mod,
166! wang_collision_kernel renamed wang_kernel
167!
168!
169! Revision 1.1  1999/11/25 16:16:06  raasch
170! Initial revision
171!
172!
173! Description:
174! ------------
175!>
176!------------------------------------------------------------------------------!
177 MODULE lagrangian_particle_model_mod
178
179    USE, INTRINSIC ::  ISO_C_BINDING
180
181    USE arrays_3d,                                                             &
182        ONLY:  de_dx, de_dy, de_dz, dzw, zu, zw,  ql_c, ql_v, ql_vp, hyp,      &
183               pt, q, exner, ql, diss, e, u, v, w, km, ql_1, ql_2, pt_p, q_p,  &
184               d_exner, u_p, v_p, w_p
185 
186    USE averaging,                                                             &
187        ONLY:  ql_c_av, pr_av, pc_av, ql_vp_av, ql_v_av
188
189    USE basic_constants_and_equations_mod,                                     &
190        ONLY: molecular_weight_of_solute, molecular_weight_of_water, magnus,   &
191              pi, rd_d_rv, rho_l, r_v, rho_s, vanthoff, l_v, kappa, g, lv_d_cp
192
193    USE control_parameters,                                                    &
194        ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, bc_dirichlet_s, &
195               cloud_droplets, constant_flux_layer, current_timestep_number,   &
196               dt_3d, dt_3d_reached, humidity,                                 &
197               dt_3d_reached_l, dt_dopts, dz, initializing_actions,            &
198               message_string, molecular_viscosity, ocean_mode,                &
199               particle_maximum_age, iran,                                     & 
200               simulated_time, topography, dopts_time_count,                   &
201               time_since_reference_point, rho_surface, u_gtrans, v_gtrans,    &
202               dz_stretch_level, dz_stretch_level_start
203
204    USE cpulog,                                                                &
205        ONLY:  cpu_log, log_point, log_point_s
206
207    USE indices,                                                               &
208        ONLY:  nx, nxl, nxlg, nxrg, nxr, ny, nyn, nys, nyng, nysg, nz, nzb,    &
209               nzb_max, nzt, wall_flags_0,nbgp, ngp_2dh_outer
210
211    USE kinds
212
213    USE pegrid
214
215    USE particle_attributes
216
217    USE pmc_particle_interface,                                                &
218        ONLY: pmcp_c_get_particle_from_parent, pmcp_p_fill_particle_win,       &
219              pmcp_c_send_particle_to_parent, pmcp_p_empty_particle_win,       &
220              pmcp_p_delete_particles_in_fine_grid_area, pmcp_g_init,          &
221              pmcp_g_print_number_of_particles
222
223    USE pmc_interface,                                                         &
224        ONLY: nested_run
225
226    USE grid_variables,                                                        &
227        ONLY:  ddx, dx, ddy, dy
228
229    USE netcdf_interface,                                                      &
230        ONLY:  netcdf_data_format, netcdf_deflate, dopts_num, id_set_pts,      &
231               id_var_dopts, id_var_time_pts, nc_stat,                         &
232               netcdf_handle_error
233
234    USE random_function_mod,                                                   &
235        ONLY:  random_function
236
237    USE statistics,                                                            &
238        ONLY:  hom
239
240    USE surface_mod,                                                           &
241        ONLY:  get_topography_top_index_ji, surf_def_h, surf_lsm_h, surf_usm_h,&
242               bc_h
243
244#if defined( __parallel )  &&  !defined( __mpifh )
245    USE MPI
246#endif
247
248#if defined( __parallel )  &&  defined( __mpifh )
249    INCLUDE "mpif.h"
250#endif     
251
252#if defined( __netcdf )
253    USE NETCDF
254#endif
255
256
257     USE arrays_3d,                                                             &
258        ONLY:
259
260    USE indices,                                                               &
261        ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_0
262
263    USE kinds
264
265    USE pegrid
266
267    IMPLICIT NONE
268
269    CHARACTER(LEN=15) ::  aero_species = 'nacl'                   !< aerosol species
270    CHARACTER(LEN=15) ::  aero_type    = 'maritime'               !< aerosol type
271    CHARACTER(LEN=15) ::  bc_par_lr    = 'cyclic'                 !< left/right boundary condition
272    CHARACTER(LEN=15) ::  bc_par_ns    = 'cyclic'                 !< north/south boundary condition
273    CHARACTER(LEN=15) ::  bc_par_b     = 'reflect'                !< bottom boundary condition
274    CHARACTER(LEN=15) ::  bc_par_t     = 'absorb'                 !< top boundary condition
275    CHARACTER(LEN=15) ::  collision_kernel   = 'none'             !< collision kernel
276
277    CHARACTER(LEN=5)  ::  splitting_function = 'gamma'            !< function for calculation critical weighting factor
278    CHARACTER(LEN=5)  ::  splitting_mode     = 'const'            !< splitting mode
279
280    CHARACTER(LEN=25) ::  particle_interpolation = 'trilinear'    !< interpolation method for calculatin the particle
281
282    INTEGER(iwp) ::  deleted_particles = 0                        !< number of deleted particles per time step   
283    INTEGER(iwp) ::  i_splitting_mode                             !< dummy for splitting mode
284    INTEGER(iwp) ::  iran_part = -1234567                         !< number for random generator   
285    INTEGER(iwp) ::  max_number_particles_per_gridbox = 100       !< namelist parameter (see documentation)
286    INTEGER(iwp) ::  isf                                          !< dummy for splitting function
287    INTEGER(iwp) ::  number_particles_per_gridbox = -1            !< namelist parameter (see documentation)
288    INTEGER(iwp) ::  number_of_sublayers = 20                     !< number of sublayers for particle velocities betwenn surface and first grid level
289    INTEGER(iwp) ::  offset_ocean_nzt = 0                         !< in case of oceans runs, the vertical index calculations need an offset
290    INTEGER(iwp) ::  offset_ocean_nzt_m1 = 0                      !< in case of oceans runs, the vertical index calculations need an offset
291    INTEGER(iwp) ::  particles_per_point = 1                      !< namelist parameter (see documentation)
292    INTEGER(iwp) ::  radius_classes = 20                          !< namelist parameter (see documentation)
293    INTEGER(iwp) ::  splitting_factor = 2                         !< namelist parameter (see documentation)
294    INTEGER(iwp) ::  splitting_factor_max = 5                     !< namelist parameter (see documentation)
295    INTEGER(iwp) ::  step_dealloc = 100                           !< namelist parameter (see documentation)
296    INTEGER(iwp) ::  total_number_of_particles                    !< total number of particles in the whole model domain
297    INTEGER(iwp) ::  trlp_count_sum                               !< parameter for particle exchange of PEs
298    INTEGER(iwp) ::  trlp_count_recv_sum                          !< parameter for particle exchange of PEs
299    INTEGER(iwp) ::  trrp_count_sum                               !< parameter for particle exchange of PEs
300    INTEGER(iwp) ::  trrp_count_recv_sum                          !< parameter for particle exchange of PEs
301    INTEGER(iwp) ::  trsp_count_sum                               !< parameter for particle exchange of PEs
302    INTEGER(iwp) ::  trsp_count_recv_sum                          !< parameter for particle exchange of PEs
303    INTEGER(iwp) ::  trnp_count_sum                               !< parameter for particle exchange of PEs
304    INTEGER(iwp) ::  trnp_count_recv_sum                          !< parameter for particle exchange of PEs
305
306    LOGICAL ::  lagrangian_particle_model = .FALSE.       !< namelist parameter (see documentation)
307    LOGICAL ::  curvature_solution_effects = .FALSE.      !< namelist parameter (see documentation)
308    LOGICAL ::  deallocate_memory = .TRUE.                !< namelist parameter (see documentation)
309    LOGICAL ::  hall_kernel = .FALSE.                     !< flag for collision kernel
310    LOGICAL ::  merging = .FALSE.                         !< namelist parameter (see documentation)
311    LOGICAL ::  random_start_position = .FALSE.           !< namelist parameter (see documentation)
312    LOGICAL ::  read_particles_from_restartfile = .TRUE.  !< namelist parameter (see documentation)
313    LOGICAL ::  seed_follows_topography = .FALSE.         !< namelist parameter (see documentation)
314    LOGICAL ::  splitting = .FALSE.                       !< namelist parameter (see documentation)
315    LOGICAL ::  use_kernel_tables = .FALSE.               !< parameter, which turns on the use of precalculated collision kernels
316    LOGICAL ::  write_particle_statistics = .FALSE.       !< namelist parameter (see documentation)
317
318    LOGICAL, DIMENSION(max_number_of_particle_groups) ::   vertical_particle_advection = .TRUE. !< Switch for vertical particle transport
319
320    REAL(wp) ::  aero_weight = 1.0_wp                      !< namelist parameter (see documentation)
321    REAL(wp) ::  dt_min_part = 0.0002_wp                   !< minimum particle time step when SGS velocities are used (s)
322    REAL(wp) ::  dt_prel = 9999999.9_wp                    !< namelist parameter (see documentation)
323    REAL(wp) ::  dt_write_particle_data = 9999999.9_wp     !< namelist parameter (see documentation)
324    REAL(wp) ::  end_time_prel = 9999999.9_wp              !< namelist parameter (see documentation)
325    REAL(wp) ::  initial_weighting_factor = 1.0_wp         !< namelist parameter (see documentation)
326    REAL(wp) ::  last_particle_release_time = 0.0_wp       !< last time of particle release
327    REAL(wp) ::  log_sigma(3) = 1.0_wp                     !< namelist parameter (see documentation)
328    REAL(wp) ::  na(3) = 0.0_wp                            !< namelist parameter (see documentation)
329    REAL(wp) ::  number_concentration = -1.0_wp            !< namelist parameter (see documentation)
330    REAL(wp) ::  radius_merge = 1.0E-7_wp                  !< namelist parameter (see documentation)
331    REAL(wp) ::  radius_split = 40.0E-6_wp                 !< namelist parameter (see documentation)
332    REAL(wp) ::  rm(3) = 1.0E-6_wp                         !< namelist parameter (see documentation)
333    REAL(wp) ::  sgs_wf_part                               !< parameter for sgs
334    REAL(wp) ::  time_write_particle_data = 0.0_wp         !< write particle data at current time on file
335    REAL(wp) ::  weight_factor_merge = -1.0_wp             !< namelist parameter (see documentation)
336    REAL(wp) ::  weight_factor_split = -1.0_wp             !< namelist parameter (see documentation)
337    REAL(wp) ::  z0_av_global                              !< horizontal mean value of z0
338
339    REAL(wp) ::  rclass_lbound !<
340    REAL(wp) ::  rclass_ubound !<
341
342    REAL(wp), PARAMETER ::  c_0 = 3.0_wp         !< parameter for lagrangian timescale
343
344    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  density_ratio = 9999999.9_wp  !< namelist parameter (see documentation)
345    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdx = 9999999.9_wp            !< namelist parameter (see documentation)
346    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdy = 9999999.9_wp            !< namelist parameter (see documentation)
347    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdz = 9999999.9_wp            !< namelist parameter (see documentation)
348    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psb = 9999999.9_wp            !< namelist parameter (see documentation)
349    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psl = 9999999.9_wp            !< namelist parameter (see documentation)
350    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psn = 9999999.9_wp            !< namelist parameter (see documentation)
351    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psr = 9999999.9_wp            !< namelist parameter (see documentation)
352    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pss = 9999999.9_wp            !< namelist parameter (see documentation)
353    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pst = 9999999.9_wp            !< namelist parameter (see documentation).
354    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  radius = 9999999.9_wp         !< namelist parameter (see documentation)
355
356    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0   !< Precalculate LOG(z/z0) 
357
358    INTEGER(iwp), PARAMETER ::  NR_2_direction_move = 10000 !<
359    INTEGER(iwp)            ::  nr_move_north               !<
360    INTEGER(iwp)            ::  nr_move_south               !<
361
362    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  move_also_north
363    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  move_also_south
364
365    REAL(wp) ::  epsilon_collision !<
366    REAL(wp) ::  urms              !<
367
368    REAL(wp), DIMENSION(:),   ALLOCATABLE ::  epsclass  !< dissipation rate class
369    REAL(wp), DIMENSION(:),   ALLOCATABLE ::  radclass  !< radius class
370    REAL(wp), DIMENSION(:),   ALLOCATABLE ::  winf      !<
371
372    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ec        !<
373    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ecf       !<
374    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gck       !<
375    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  hkernel   !<
376    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  hwratio   !<
377
378    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ckernel !<
379
380    INTEGER(iwp), PARAMETER         :: PHASE_INIT    = 1  !<
381    INTEGER(iwp), PARAMETER, PUBLIC :: PHASE_RELEASE = 2  !<
382
383    SAVE
384
385    PRIVATE
386
387    PUBLIC lpm_parin,     &
388           lpm_header,    &
389           lpm_init_arrays,&
390           lpm_init,      &
391           lpm_actions,   &
392           lpm_data_output_ptseries, &
393           lpm_interaction_droplets_ptq, &
394           lpm_rrd_local_particles, &
395           lpm_wrd_local, &
396           lpm_rrd_global, &
397           lpm_wrd_global, &
398           lpm_rrd_local, &
399           lpm_check_parameters
400
401    PUBLIC lagrangian_particle_model
402
403    INTERFACE lpm_check_parameters
404       MODULE PROCEDURE lpm_check_parameters
405    END INTERFACE lpm_check_parameters
406
407    INTERFACE lpm_parin
408       MODULE PROCEDURE lpm_parin
409    END INTERFACE lpm_parin
410
411    INTERFACE lpm_header
412       MODULE PROCEDURE lpm_header
413    END INTERFACE lpm_header
414
415    INTERFACE lpm_init_arrays
416       MODULE PROCEDURE lpm_init_arrays
417    END INTERFACE lpm_init_arrays
418 
419    INTERFACE lpm_init
420       MODULE PROCEDURE lpm_init
421    END INTERFACE lpm_init
422
423    INTERFACE lpm_actions
424       MODULE PROCEDURE lpm_actions
425    END INTERFACE lpm_actions
426
427    INTERFACE lpm_data_output_ptseries
428       MODULE PROCEDURE lpm_data_output_ptseries
429    END INTERFACE
430
431    INTERFACE lpm_rrd_local_particles
432       MODULE PROCEDURE lpm_rrd_local_particles
433    END INTERFACE lpm_rrd_local_particles
434
435    INTERFACE lpm_rrd_global
436       MODULE PROCEDURE lpm_rrd_global
437    END INTERFACE lpm_rrd_global
438
439    INTERFACE lpm_rrd_local
440       MODULE PROCEDURE lpm_rrd_local
441    END INTERFACE lpm_rrd_local
442
443    INTERFACE lpm_wrd_local
444       MODULE PROCEDURE lpm_wrd_local
445    END INTERFACE lpm_wrd_local
446
447    INTERFACE lpm_wrd_global
448       MODULE PROCEDURE lpm_wrd_global
449    END INTERFACE lpm_wrd_global
450
451    INTERFACE lpm_advec
452       MODULE PROCEDURE lpm_advec
453    END INTERFACE lpm_advec
454
455    INTERFACE lpm_calc_liquid_water_content
456       MODULE PROCEDURE lpm_calc_liquid_water_content
457    END INTERFACE
458
459    INTERFACE lpm_interaction_droplets_ptq
460       MODULE PROCEDURE lpm_interaction_droplets_ptq
461       MODULE PROCEDURE lpm_interaction_droplets_ptq_ij
462    END INTERFACE lpm_interaction_droplets_ptq
463
464    INTERFACE lpm_boundary_conds
465       MODULE PROCEDURE lpm_boundary_conds
466    END INTERFACE lpm_boundary_conds
467
468    INTERFACE lpm_droplet_condensation
469       MODULE PROCEDURE lpm_droplet_condensation
470    END INTERFACE
471
472    INTERFACE lpm_droplet_collision
473       MODULE PROCEDURE lpm_droplet_collision
474    END INTERFACE lpm_droplet_collision
475
476    INTERFACE lpm_init_kernels
477       MODULE PROCEDURE lpm_init_kernels
478    END INTERFACE lpm_init_kernels
479
480    INTERFACE lpm_splitting
481       MODULE PROCEDURE lpm_splitting
482    END INTERFACE lpm_splitting
483
484    INTERFACE lpm_merging
485       MODULE PROCEDURE lpm_merging
486    END INTERFACE lpm_merging
487
488    INTERFACE lpm_exchange_horiz
489       MODULE PROCEDURE lpm_exchange_horiz
490    END INTERFACE lpm_exchange_horiz
491
492    INTERFACE lpm_move_particle
493       MODULE PROCEDURE lpm_move_particle
494    END INTERFACE lpm_move_particle
495
496    INTERFACE realloc_particles_array
497       MODULE PROCEDURE realloc_particles_array
498    END INTERFACE realloc_particles_array
499
500    INTERFACE dealloc_particles_array
501       MODULE PROCEDURE dealloc_particles_array
502    END INTERFACE dealloc_particles_array
503
504    INTERFACE lpm_sort_and_delete
505       MODULE PROCEDURE lpm_sort_and_delete
506    END INTERFACE lpm_sort_and_delete
507
508    INTERFACE lpm_sort_timeloop_done
509       MODULE PROCEDURE lpm_sort_timeloop_done
510    END INTERFACE lpm_sort_timeloop_done
511
512    INTERFACE lpm_pack
513       MODULE PROCEDURE lpm_pack
514    END INTERFACE lpm_pack
515
516 CONTAINS
517 
518
519!------------------------------------------------------------------------------!
520! Description:
521! ------------
522!> Parin for &particle_parameters for the Lagrangian particle model
523!------------------------------------------------------------------------------!
524 SUBROUTINE lpm_parin
525 
526    CHARACTER (LEN=80) ::  line  !<
527
528    NAMELIST /particles_par/ &
529       aero_species, &
530       aero_type, &
531       aero_weight, &
532       alloc_factor, &
533       bc_par_b, &
534       bc_par_lr, &
535       bc_par_ns, &
536       bc_par_t, &
537       collision_kernel, &
538       curvature_solution_effects, &
539       deallocate_memory, &
540       density_ratio, &
541       dissipation_classes, &
542       dt_dopts, &
543       dt_min_part, &
544       dt_prel, &
545       dt_write_particle_data, &
546       end_time_prel, &
547       initial_weighting_factor, &
548       log_sigma, &
549       max_number_particles_per_gridbox, &
550       merging, &
551       na, &
552       number_concentration, &
553       number_of_particle_groups, &
554       number_particles_per_gridbox, &
555       particles_per_point, &
556       particle_advection_start, &
557       particle_interpolation, &
558       particle_maximum_age, &
559       pdx, &
560       pdy, &
561       pdz, &
562       psb, &
563       psl, &
564       psn, &
565       psr, &
566       pss, &
567       pst, &
568       radius, &
569       radius_classes, &
570       radius_merge, &
571       radius_split, &
572       random_start_position, &
573       read_particles_from_restartfile, &
574       rm, &
575       seed_follows_topography, &
576       splitting, &
577       splitting_factor, &
578       splitting_factor_max, &
579       splitting_function, &
580       splitting_mode, &
581       step_dealloc, &
582       use_sgs_for_particles, &
583       vertical_particle_advection, &
584       weight_factor_merge, &
585       weight_factor_split, &
586       write_particle_statistics
587
588       NAMELIST /particle_parameters/ &
589       aero_species, &
590       aero_type, &
591       aero_weight, &
592       alloc_factor, &
593       bc_par_b, &
594       bc_par_lr, &
595       bc_par_ns, &
596       bc_par_t, &
597       collision_kernel, &
598       curvature_solution_effects, &
599       deallocate_memory, &
600       density_ratio, &
601       dissipation_classes, &
602       dt_dopts, &
603       dt_min_part, &
604       dt_prel, &
605       dt_write_particle_data, &
606       end_time_prel, &
607       initial_weighting_factor, &
608       log_sigma, &
609       max_number_particles_per_gridbox, &
610       merging, &
611       na, &
612       number_concentration, &
613       number_of_particle_groups, &
614       number_particles_per_gridbox, &
615       particles_per_point, &
616       particle_advection_start, &
617       particle_interpolation, &
618       particle_maximum_age, &
619       pdx, &
620       pdy, &
621       pdz, &
622       psb, &
623       psl, &
624       psn, &
625       psr, &
626       pss, &
627       pst, &
628       radius, &
629       radius_classes, &
630       radius_merge, &
631       radius_split, &
632       random_start_position, &
633       read_particles_from_restartfile, &
634       rm, &
635       seed_follows_topography, &
636       splitting, &
637       splitting_factor, &
638       splitting_factor_max, &
639       splitting_function, &
640       splitting_mode, &
641       step_dealloc, &
642       use_sgs_for_particles, &
643       vertical_particle_advection, &
644       weight_factor_merge, &
645       weight_factor_split, &
646       write_particle_statistics
647
648!
649!-- Position the namelist-file at the beginning (it was already opened in
650!-- parin), search for the namelist-group of the package and position the
651!-- file at this line. Do the same for each optionally used package.
652    line = ' '
653   
654!
655!-- Try to find particles package
656    REWIND ( 11 )
657    line = ' '
658    DO   WHILE ( INDEX( line, '&particle_parameters' ) == 0 )
659       READ ( 11, '(A)', END=12 )  line
660    ENDDO
661    BACKSPACE ( 11 )
662!
663!-- Read user-defined namelist
664    READ ( 11, particle_parameters, ERR = 10 )
665!
666!-- Set flag that indicates that particles are switched on
667    particle_advection = .TRUE.
668   
669    GOTO 14
670
67110  BACKSPACE( 11 )
672    READ( 11 , '(A)') line
673    CALL parin_fail_message( 'particle_parameters', line )
674!
675!-- Try to find particles package (old namelist)
67612  REWIND ( 11 )
677    line = ' '
678    DO WHILE ( INDEX( line, '&particles_par' ) == 0 )
679       READ ( 11, '(A)', END=14 )  line
680    ENDDO
681    BACKSPACE ( 11 )
682!
683!-- Read user-defined namelist
684    READ ( 11, particles_par, ERR = 13, END = 14 )
685
686    message_string = 'namelist particles_par is deprecated and will be ' //    &
687                     'removed in near future. Please use namelist ' //         &
688                     'particle_parameters instead'
689    CALL message( 'package_parin', 'PA0487', 0, 1, 0, 6, 0 )
690
691!
692!-- Set flag that indicates that particles are switched on
693    particle_advection = .TRUE.
694
695    GOTO 14
696
69713    BACKSPACE( 11 )
698       READ( 11 , '(A)') line
699       CALL parin_fail_message( 'particles_par', line )
700
70114 CONTINUE
702
703 END SUBROUTINE lpm_parin
704 
705!------------------------------------------------------------------------------!
706! Description:
707! ------------
708!> Writes used particle attributes in header file.
709!------------------------------------------------------------------------------!
710 SUBROUTINE lpm_header ( io )
711
712    CHARACTER (LEN=40) ::  output_format       !< netcdf format
713 
714    INTEGER(iwp) ::  i               !<
715    INTEGER(iwp), INTENT(IN) ::  io  !< Unit of the output file
716
717 
718     IF ( humidity  .AND.  cloud_droplets )  THEN
719       WRITE ( io, 433 )
720       IF ( curvature_solution_effects )  WRITE ( io, 434 )
721       IF ( collision_kernel /= 'none' )  THEN
722          WRITE ( io, 435 )  TRIM( collision_kernel )
723          IF ( collision_kernel(6:9) == 'fast' )  THEN
724             WRITE ( io, 436 )  radius_classes, dissipation_classes
725          ENDIF
726       ELSE
727          WRITE ( io, 437 )
728       ENDIF
729    ENDIF
730 
731    IF ( particle_advection )  THEN
732!
733!--    Particle attributes
734       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
735                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
736                          end_time_prel
737       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
738       IF ( random_start_position )  WRITE ( io, 481 )
739       IF ( seed_follows_topography )  WRITE ( io, 496 )
740       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
741       WRITE ( io, 495 )  total_number_of_particles
742       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
743          WRITE ( io, 485 )  dt_write_particle_data
744          IF ( netcdf_data_format > 1 )  THEN
745             output_format = 'netcdf (64 bit offset) and binary'
746          ELSE
747             output_format = 'netcdf and binary'
748          ENDIF
749          IF ( netcdf_deflate == 0 )  THEN
750             WRITE ( io, 344 )  output_format
751          ELSE
752             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
753          ENDIF
754       ENDIF
755       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
756       IF ( write_particle_statistics )  WRITE ( io, 486 )
757
758       WRITE ( io, 487 )  number_of_particle_groups
759
760       DO  i = 1, number_of_particle_groups
761          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
762             WRITE ( io, 490 )  i, 0.0_wp
763             WRITE ( io, 492 )
764          ELSE
765             WRITE ( io, 490 )  i, radius(i)
766             IF ( density_ratio(i) /= 0.0_wp )  THEN
767                WRITE ( io, 491 )  density_ratio(i)
768             ELSE
769                WRITE ( io, 492 )
770             ENDIF
771          ENDIF
772          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
773                             pdx(i), pdy(i), pdz(i)
774          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
775       ENDDO
776
777    ENDIF
778   
779344 FORMAT ('       Output format: ',A/)
780354 FORMAT ('       Output format: ',A, '   compressed with level: ',I1/)
781
782433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
783                 'icle model')
784434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
785                 ' droplets < 1.0E-6 m')
786435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
787436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
788                    'are used'/ &
789            '          number of radius classes:       ',I3,'    interval ', &
790                       '[1.0E-6,2.0E-4] m'/ &
791            '          number of dissipation classes:   ',I2,'    interval ', &
792                       '[0,1000] cm**2/s**3')
793437 FORMAT ('    Droplet collision is switched off')
794
795480 FORMAT ('    Particles:'/ &
796            '    ---------'// &
797            '       Particle advection is active (switched on at t = ', F7.1, &
798                    ' s)'/ &
799            '       Start of new particle generations every  ',F6.1,' s'/ &
800            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
801            '                            bottom:     ', A, ' top:         ', A/&
802            '       Maximum particle age:                 ',F9.1,' s'/ &
803            '       Advection stopped at t = ',F9.1,' s'/)
804481 FORMAT ('       Particles have random start positions'/)
805482 FORMAT ('          Particles are advected only horizontally'/)
806485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
807486 FORMAT ('       Particle statistics are written on file'/)
808487 FORMAT ('       Number of particle groups: ',I2/)
809488 FORMAT ('       SGS velocity components are used for particle advection'/ &
810            '          minimum timestep for advection:', F8.5/)
811489 FORMAT ('       Number of particles simultaneously released at each ', &
812                    'point: ', I5/)
813490 FORMAT ('       Particle group ',I2,':'/ &
814            '          Particle radius: ',E10.3, 'm')
815491 FORMAT ('          Particle inertia is activated'/ &
816            '             density_ratio (rho_fluid/rho_particle) =',F6.3/)
817492 FORMAT ('          Particles are advected only passively (no inertia)'/)
818493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
819            '                                         y:',F8.1,' - ',F8.1,' m'/&
820            '                                         z:',F8.1,' - ',F8.1,' m'/&
821            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
822                       ' m  dz = ',F8.1,' m'/)
823494 FORMAT ('       Output of particle time series in NetCDF format every ', &
824                    F8.2,' s'/)
825495 FORMAT ('       Number of particles in total domain: ',I10/)
826496 FORMAT ('       Initial vertical particle positions are interpreted ', &
827                    'as relative to the given topography')
828   
829 END SUBROUTINE lpm_header
830 
831!------------------------------------------------------------------------------!
832! Description:
833! ------------
834!> Writes used particle attributes in header file.
835!------------------------------------------------------------------------------! 
836 SUBROUTINE lpm_check_parameters
837 
838!
839!-- Collision kernels:
840    SELECT CASE ( TRIM( collision_kernel ) )
841
842       CASE ( 'hall', 'hall_fast' )
843          hall_kernel = .TRUE.
844
845       CASE ( 'wang', 'wang_fast' )
846          wang_kernel = .TRUE.
847
848       CASE ( 'none' )
849
850
851       CASE DEFAULT
852          message_string = 'unknown collision kernel: collision_kernel = "' // &
853                           TRIM( collision_kernel ) // '"'
854          CALL message( 'check_parameters', 'PA0350', 1, 2, 0, 6, 0 )
855
856    END SELECT
857    IF ( collision_kernel(6:9) == 'fast' )  use_kernel_tables = .TRUE.
858
859!
860!-- Subgrid scale velocites with the simple interpolation method for resolved
861!-- velocites is not implemented for passive particles. However, for cloud
862!-- it can be combined as the sgs-velocites for active particles are
863!-- calculated differently, i.e. no subboxes are needed.
864    IF ( .NOT. TRIM(particle_interpolation) == 'trilinear'  .AND.              &
865       use_sgs_for_particles .AND.  .NOT. cloud_droplets )  THEN
866          message_string = 'subrgrid scale velocities in combination with ' // &
867                           'simple interpolation method is not '            // &
868                           'implemented'
869          CALL message( 'check_parameters', 'PA0659', 1, 2, 0, 6, 0 )
870    ENDIF
871
872 END SUBROUTINE
873 
874!------------------------------------------------------------------------------!
875! Description:
876! ------------
877!> Initialize arrays for lpm
878!------------------------------------------------------------------------------!   
879 SUBROUTINE lpm_init_arrays
880 
881    IF ( cloud_droplets )  THEN
882!
883!--    Liquid water content, change in liquid water content
884       ALLOCATE ( ql_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
885                  ql_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
886!
887!--    Real volume of particles (with weighting), volume of particles
888       ALLOCATE ( ql_v(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
889                     ql_vp(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
890    ENDIF
891   
892!
893!--    Initial assignment of the pointers   
894    IF ( cloud_droplets )  THEN
895       ql   => ql_1
896       ql_c => ql_2
897    ENDIF
898   
899 END SUBROUTINE lpm_init_arrays
900 
901!------------------------------------------------------------------------------!
902! Description:
903! ------------
904!> Initialize Lagrangian particle model
905!------------------------------------------------------------------------------!
906 SUBROUTINE lpm_init
907
908    INTEGER(iwp) ::  i                           !<
909    INTEGER(iwp) ::  j                           !<
910    INTEGER(iwp) ::  k                           !<
911
912    REAL(wp) ::  div                             !<
913    REAL(wp) ::  height_int                      !<
914    REAL(wp) ::  height_p                        !<
915    REAL(wp) ::  z_p                             !<
916    REAL(wp) ::  z0_av_local                     !<
917
918!
919!-- In case of oceans runs, the vertical index calculations need an offset,
920!-- because otherwise the k indices will become negative
921    IF ( ocean_mode )  THEN
922       offset_ocean_nzt    = nzt
923       offset_ocean_nzt_m1 = nzt - 1
924    ENDIF
925
926!
927!-- Define block offsets for dividing a gridcell in 8 sub cells
928!-- See documentation for List of subgrid boxes
929!-- See pack_and_sort in lpm_pack_arrays.f90 for assignment of the subgrid boxes
930    block_offset(0) = block_offset_def ( 0, 0, 0)
931    block_offset(1) = block_offset_def ( 0, 0,-1)
932    block_offset(2) = block_offset_def ( 0,-1, 0)
933    block_offset(3) = block_offset_def ( 0,-1,-1)
934    block_offset(4) = block_offset_def (-1, 0, 0)
935    block_offset(5) = block_offset_def (-1, 0,-1)
936    block_offset(6) = block_offset_def (-1,-1, 0)
937    block_offset(7) = block_offset_def (-1,-1,-1)
938!
939!-- Check the number of particle groups.
940    IF ( number_of_particle_groups > max_number_of_particle_groups )  THEN
941       WRITE( message_string, * ) 'max_number_of_particle_groups =',           &
942                                  max_number_of_particle_groups ,              &
943                                  '&number_of_particle_groups reset to ',      &
944                                  max_number_of_particle_groups
945       CALL message( 'lpm_init', 'PA0213', 0, 1, 0, 6, 0 )
946       number_of_particle_groups = max_number_of_particle_groups
947    ENDIF
948!
949!-- Check if downward-facing walls exist. This case, reflection boundary
950!-- conditions (as well as subgrid-scale velocities) may do not work
951!-- propably (not realized so far).
952    IF ( surf_def_h(1)%ns >= 1 )  THEN
953       WRITE( message_string, * ) 'Overhanging topography do not work '//      &
954                                  'with particles'
955       CALL message( 'lpm_init', 'PA0212', 0, 1, 0, 6, 0 )
956
957    ENDIF
958
959!
960!-- Set default start positions, if necessary
961    IF ( psl(1) == 9999999.9_wp )  psl(1) = 0.0_wp
962    IF ( psr(1) == 9999999.9_wp )  psr(1) = ( nx +1 ) * dx
963    IF ( pss(1) == 9999999.9_wp )  pss(1) = 0.0_wp
964    IF ( psn(1) == 9999999.9_wp )  psn(1) = ( ny +1 ) * dy
965    IF ( psb(1) == 9999999.9_wp )  psb(1) = zu(nz/2)
966    IF ( pst(1) == 9999999.9_wp )  pst(1) = psb(1)
967
968    IF ( pdx(1) == 9999999.9_wp  .OR.  pdx(1) == 0.0_wp )  pdx(1) = dx
969    IF ( pdy(1) == 9999999.9_wp  .OR.  pdy(1) == 0.0_wp )  pdy(1) = dy
970    IF ( pdz(1) == 9999999.9_wp  .OR.  pdz(1) == 0.0_wp )  pdz(1) = zu(2) - zu(1)
971
972!
973!-- If number_particles_per_gridbox is set, the parametres pdx, pdy and pdz are
974!-- calculated diagnostically. Therfore an isotropic distribution is prescribed.
975    IF ( number_particles_per_gridbox /= -1 .AND.   &
976         number_particles_per_gridbox >= 1 )    THEN
977       pdx(1) = (( dx * dy * ( zu(2) - zu(1) ) ) /  &
978             REAL(number_particles_per_gridbox))**0.3333333_wp
979!
980!--    Ensure a smooth value (two significant digits) of distance between
981!--    particles (pdx, pdy, pdz).
982       div = 1000.0_wp
983       DO  WHILE ( pdx(1) < div )
984          div = div / 10.0_wp
985       ENDDO
986       pdx(1) = NINT( pdx(1) * 100.0_wp / div ) * div / 100.0_wp
987       pdy(1) = pdx(1)
988       pdz(1) = pdx(1)
989
990    ENDIF
991
992    DO  j = 2, number_of_particle_groups
993       IF ( psl(j) == 9999999.9_wp )  psl(j) = psl(j-1)
994       IF ( psr(j) == 9999999.9_wp )  psr(j) = psr(j-1)
995       IF ( pss(j) == 9999999.9_wp )  pss(j) = pss(j-1)
996       IF ( psn(j) == 9999999.9_wp )  psn(j) = psn(j-1)
997       IF ( psb(j) == 9999999.9_wp )  psb(j) = psb(j-1)
998       IF ( pst(j) == 9999999.9_wp )  pst(j) = pst(j-1)
999       IF ( pdx(j) == 9999999.9_wp  .OR.  pdx(j) == 0.0_wp )  pdx(j) = pdx(j-1)
1000       IF ( pdy(j) == 9999999.9_wp  .OR.  pdy(j) == 0.0_wp )  pdy(j) = pdy(j-1)
1001       IF ( pdz(j) == 9999999.9_wp  .OR.  pdz(j) == 0.0_wp )  pdz(j) = pdz(j-1)
1002    ENDDO
1003
1004!
1005!-- Allocate arrays required for calculating particle SGS velocities.
1006!-- Initialize prefactor required for stoachastic Weil equation.
1007    IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets )  THEN
1008       ALLOCATE( de_dx(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
1009                 de_dy(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
1010                 de_dz(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1011
1012       de_dx = 0.0_wp
1013       de_dy = 0.0_wp
1014       de_dz = 0.0_wp             
1015                 
1016       sgs_wf_part = 1.0_wp / 3.0_wp
1017    ENDIF
1018
1019!
1020!-- Allocate array required for logarithmic vertical interpolation of
1021!-- horizontal particle velocities between the surface and the first vertical
1022!-- grid level. In order to avoid repeated CPU cost-intensive CALLS of
1023!-- intrinsic FORTRAN procedure LOG(z/z0), LOG(z/z0) is precalculated for
1024!-- several heights. Splitting into 20 sublayers turned out to be sufficient.
1025!-- To obtain exact height levels of particles, linear interpolation is applied
1026!-- (see lpm_advec.f90).
1027    IF ( constant_flux_layer )  THEN
1028
1029       ALLOCATE ( log_z_z0(0:number_of_sublayers) )
1030       z_p = zu(nzb+1) - zw(nzb)
1031
1032!
1033!--    Calculate horizontal mean value of z0 used for logartihmic
1034!--    interpolation. Note: this is not exact for heterogeneous z0.
1035!--    However, sensitivity studies showed that the effect is
1036!--    negligible.
1037       z0_av_local  = SUM( surf_def_h(0)%z0 ) + SUM( surf_lsm_h%z0 ) +         &
1038                      SUM( surf_usm_h%z0 )
1039       z0_av_global = 0.0_wp
1040
1041#if defined( __parallel )
1042       CALL MPI_ALLREDUCE(z0_av_local, z0_av_global, 1, MPI_REAL, MPI_SUM, &
1043                          comm2d, ierr )
1044#else
1045       z0_av_global = z0_av_local
1046#endif
1047
1048       z0_av_global = z0_av_global  / ( ( ny + 1 ) * ( nx + 1 ) )
1049!
1050!--    Horizontal wind speed is zero below and at z0
1051       log_z_z0(0) = 0.0_wp
1052!
1053!--    Calculate vertical depth of the sublayers
1054       height_int  = ( z_p - z0_av_global ) / REAL( number_of_sublayers, KIND=wp )
1055!
1056!--    Precalculate LOG(z/z0)
1057       height_p    = z0_av_global
1058       DO  k = 1, number_of_sublayers
1059
1060          height_p    = height_p + height_int
1061          log_z_z0(k) = LOG( height_p / z0_av_global )
1062
1063       ENDDO
1064
1065    ENDIF
1066
1067!
1068!-- Check boundary condition and set internal variables
1069    SELECT CASE ( bc_par_b )
1070
1071       CASE ( 'absorb' )
1072          ibc_par_b = 1
1073
1074       CASE ( 'reflect' )
1075          ibc_par_b = 2
1076
1077       CASE DEFAULT
1078          WRITE( message_string, * )  'unknown boundary condition ',           &
1079                                       'bc_par_b = "', TRIM( bc_par_b ), '"'
1080          CALL message( 'lpm_init', 'PA0217', 1, 2, 0, 6, 0 )
1081
1082    END SELECT
1083    SELECT CASE ( bc_par_t )
1084
1085       CASE ( 'absorb' )
1086          ibc_par_t = 1
1087
1088       CASE ( 'reflect' )
1089          ibc_par_t = 2
1090
1091       CASE ( 'nested' )
1092          ibc_par_t = 3
1093
1094       CASE DEFAULT
1095          WRITE( message_string, * ) 'unknown boundary condition ',            &
1096                                     'bc_par_t = "', TRIM( bc_par_t ), '"'
1097          CALL message( 'lpm_init', 'PA0218', 1, 2, 0, 6, 0 )
1098
1099    END SELECT
1100    SELECT CASE ( bc_par_lr )
1101
1102       CASE ( 'cyclic' )
1103          ibc_par_lr = 0
1104
1105       CASE ( 'absorb' )
1106          ibc_par_lr = 1
1107
1108       CASE ( 'reflect' )
1109          ibc_par_lr = 2
1110
1111       CASE ( 'nested' )
1112          ibc_par_lr = 3
1113
1114       CASE DEFAULT
1115          WRITE( message_string, * ) 'unknown boundary condition ',   &
1116                                     'bc_par_lr = "', TRIM( bc_par_lr ), '"'
1117          CALL message( 'lpm_init', 'PA0219', 1, 2, 0, 6, 0 )
1118
1119    END SELECT
1120    SELECT CASE ( bc_par_ns )
1121
1122       CASE ( 'cyclic' )
1123          ibc_par_ns = 0
1124
1125       CASE ( 'absorb' )
1126          ibc_par_ns = 1
1127
1128       CASE ( 'reflect' )
1129          ibc_par_ns = 2
1130
1131       CASE ( 'nested' )
1132          ibc_par_ns = 3
1133
1134       CASE DEFAULT
1135          WRITE( message_string, * ) 'unknown boundary condition ',   &
1136                                     'bc_par_ns = "', TRIM( bc_par_ns ), '"'
1137          CALL message( 'lpm_init', 'PA0220', 1, 2, 0, 6, 0 )
1138
1139    END SELECT
1140    SELECT CASE ( splitting_mode )
1141
1142       CASE ( 'const' )
1143          i_splitting_mode = 1
1144
1145       CASE ( 'cl_av' )
1146          i_splitting_mode = 2
1147
1148       CASE ( 'gb_av' )
1149          i_splitting_mode = 3
1150
1151       CASE DEFAULT
1152          WRITE( message_string, * )  'unknown splitting_mode = "',            &
1153                                      TRIM( splitting_mode ), '"'
1154          CALL message( 'lpm_init', 'PA0146', 1, 2, 0, 6, 0 )
1155
1156    END SELECT
1157    SELECT CASE ( splitting_function )
1158
1159       CASE ( 'gamma' )
1160          isf = 1
1161
1162       CASE ( 'log' )
1163          isf = 2
1164
1165       CASE ( 'exp' )
1166          isf = 3
1167
1168       CASE DEFAULT
1169          WRITE( message_string, * )  'unknown splitting function = "',        &
1170                                       TRIM( splitting_function ), '"'
1171          CALL message( 'lpm_init', 'PA0147', 1, 2, 0, 6, 0 )
1172
1173    END SELECT
1174!
1175!-- Initialize collision kernels
1176    IF ( collision_kernel /= 'none' )  CALL lpm_init_kernels
1177!
1178!-- For the first model run of a possible job chain initialize the
1179!-- particles, otherwise read the particle data from restart file.
1180    IF ( TRIM( initializing_actions ) == 'read_restart_data'  &
1181         .AND.  read_particles_from_restartfile )  THEN
1182       CALL lpm_rrd_local_particles
1183    ELSE
1184!
1185!--    Allocate particle arrays and set attributes of the initial set of
1186!--    particles, which can be also periodically released at later times.
1187       ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
1188                 grid_particles(nzb+1:nzt,nys:nyn,nxl:nxr) )
1189
1190       number_of_particles = 0
1191       prt_count           = 0
1192!
1193!--    initialize counter for particle IDs
1194       grid_particles%id_counter = 1
1195!
1196!--    Initialize all particles with dummy values (otherwise errors may
1197!--    occur within restart runs). The reason for this is still not clear
1198!--    and may be presumably caused by errors in the respective user-interface.
1199       zero_particle = particle_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
1200                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
1201                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
1202                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
1203                                      0, 0, 0_idp, .FALSE., -1 )
1204
1205       particle_groups = particle_groups_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp )
1206!
1207!--    Set values for the density ratio and radius for all particle
1208!--    groups, if necessary
1209       IF ( density_ratio(1) == 9999999.9_wp )  density_ratio(1) = 0.0_wp
1210       IF ( radius(1)        == 9999999.9_wp )  radius(1) = 0.0_wp
1211       DO  i = 2, number_of_particle_groups
1212          IF ( density_ratio(i) == 9999999.9_wp )  THEN
1213             density_ratio(i) = density_ratio(i-1)
1214          ENDIF
1215          IF ( radius(i) == 9999999.9_wp )  radius(i) = radius(i-1)
1216       ENDDO
1217
1218       DO  i = 1, number_of_particle_groups
1219          IF ( density_ratio(i) /= 0.0_wp  .AND.  radius(i) == 0 )  THEN
1220             WRITE( message_string, * ) 'particle group #', i, ' has a',       &
1221                                        'density ratio /= 0 but radius = 0'
1222             CALL message( 'lpm_init', 'PA0215', 1, 2, 0, 6, 0 )
1223          ENDIF
1224          particle_groups(i)%density_ratio = density_ratio(i)
1225          particle_groups(i)%radius        = radius(i)
1226       ENDDO
1227!
1228!--    Set a seed value for the random number generator to be exclusively
1229!--    used for the particle code. The generated random numbers should be
1230!--    different on the different PEs.
1231       iran_part = iran_part + myid
1232!
1233!--    Create the particle set, and set the initial particles
1234       CALL lpm_create_particle( phase_init )
1235       last_particle_release_time = particle_advection_start
1236!
1237!--    User modification of initial particles
1238       CALL user_lpm_init
1239!
1240!--    Open file for statistical informations about particle conditions
1241       IF ( write_particle_statistics )  THEN
1242          CALL check_open( 80 )
1243          WRITE ( 80, 8000 )  current_timestep_number, simulated_time,         &
1244                              number_of_particles
1245          CALL close_file( 80 )
1246       ENDIF
1247
1248    ENDIF
1249
1250    IF ( nested_run )  CALL pmcp_g_init
1251!
1252!-- To avoid programm abort, assign particles array to the local version of
1253!-- first grid cell
1254    number_of_particles = prt_count(nzb+1,nys,nxl)
1255    particles => grid_particles(nzb+1,nys,nxl)%particles(1:number_of_particles)
1256!
1257!-- Formats
12588000 FORMAT (I6,1X,F7.2,4X,I10,71X,I10)
1259
1260 END SUBROUTINE lpm_init
1261 
1262!------------------------------------------------------------------------------!
1263! Description:
1264! ------------
1265!> Create Lagrangian particles
1266!------------------------------------------------------------------------------! 
1267 SUBROUTINE lpm_create_particle (phase)
1268
1269    INTEGER(iwp)               ::  alloc_size  !< relative increase of allocated memory for particles
1270    INTEGER(iwp)               ::  i           !< loop variable ( particle groups )
1271    INTEGER(iwp)               ::  ip          !< index variable along x
1272    INTEGER(iwp)               ::  j           !< loop variable ( particles per point )
1273    INTEGER(iwp)               ::  jp          !< index variable along y
1274    INTEGER(iwp)               ::  k           !< index variable along z
1275    INTEGER(iwp)               ::  k_surf      !< index of surface grid point
1276    INTEGER(iwp)               ::  kp          !< index variable along z
1277    INTEGER(iwp)               ::  loop_stride !< loop variable for initialization
1278    INTEGER(iwp)               ::  n           !< loop variable ( number of particles )
1279    INTEGER(iwp)               ::  new_size    !< new size of allocated memory for particles
1280
1281    INTEGER(iwp), INTENT(IN)   ::  phase       !< mode of inititialization
1282
1283    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  local_count !< start address of new particle
1284    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  local_start !< start address of new particle
1285
1286    LOGICAL                    ::  first_stride !< flag for initialization
1287
1288    REAL(wp)                   ::  pos_x      !< increment for particle position in x
1289    REAL(wp)                   ::  pos_y      !< increment for particle position in y
1290    REAL(wp)                   ::  pos_z      !< increment for particle position in z
1291    REAL(wp)                   ::  rand_contr !< dummy argument for random position
1292
1293    TYPE(particle_type),TARGET ::  tmp_particle !< temporary particle used for initialization
1294
1295!
1296!-- Calculate particle positions and store particle attributes, if
1297!-- particle is situated on this PE
1298    DO  loop_stride = 1, 2
1299       first_stride = (loop_stride == 1)
1300       IF ( first_stride )   THEN
1301          local_count = 0           ! count number of particles
1302       ELSE
1303          local_count = prt_count   ! Start address of new particles
1304       ENDIF
1305
1306!
1307!--    Calculate initial_weighting_factor diagnostically
1308       IF ( number_concentration /= -1.0_wp .AND. number_concentration > 0.0_wp ) THEN
1309          initial_weighting_factor =  number_concentration  *                        &
1310                                      pdx(1) * pdy(1) * pdz(1)
1311       END IF
1312
1313       n = 0
1314       DO  i = 1, number_of_particle_groups
1315          pos_z = psb(i)
1316          DO WHILE ( pos_z <= pst(i) )
1317             IF ( pos_z >= zw(0) .AND.  pos_z < zw(nzt) )  THEN
1318                pos_y = pss(i)
1319                DO WHILE ( pos_y <= psn(i) )
1320                   IF ( pos_y >= nys * dy  .AND.                  &
1321                        pos_y <  ( nyn + 1 ) * dy  ) THEN
1322                      pos_x = psl(i)
1323               xloop: DO WHILE ( pos_x <= psr(i) )
1324                         IF ( pos_x >= nxl * dx  .AND.            &
1325                              pos_x <  ( nxr + 1) * dx ) THEN
1326                            DO  j = 1, particles_per_point
1327                               n = n + 1
1328                               tmp_particle%x             = pos_x
1329                               tmp_particle%y             = pos_y
1330                               tmp_particle%z             = pos_z
1331                               tmp_particle%age           = 0.0_wp
1332                               tmp_particle%age_m         = 0.0_wp
1333                               tmp_particle%dt_sum        = 0.0_wp
1334                               tmp_particle%e_m           = 0.0_wp
1335                               tmp_particle%rvar1         = 0.0_wp
1336                               tmp_particle%rvar2         = 0.0_wp
1337                               tmp_particle%rvar3         = 0.0_wp
1338                               tmp_particle%speed_x       = 0.0_wp
1339                               tmp_particle%speed_y       = 0.0_wp
1340                               tmp_particle%speed_z       = 0.0_wp
1341                               tmp_particle%origin_x      = pos_x
1342                               tmp_particle%origin_y      = pos_y
1343                               tmp_particle%origin_z      = pos_z
1344                               IF ( curvature_solution_effects )  THEN
1345                                  tmp_particle%aux1      = 0.0_wp    ! dry aerosol radius
1346                                  tmp_particle%aux2      = dt_3d     ! last Rosenbrock timestep
1347                               ELSE
1348                                  tmp_particle%aux1      = 0.0_wp    ! free to use
1349                                  tmp_particle%aux2      = 0.0_wp    ! free to use
1350                               ENDIF
1351                               tmp_particle%radius        = particle_groups(i)%radius
1352                               tmp_particle%weight_factor = initial_weighting_factor
1353                               tmp_particle%class         = 1
1354                               tmp_particle%group         = i
1355                               tmp_particle%id            = 0_idp
1356                               tmp_particle%particle_mask = .TRUE.
1357                               tmp_particle%block_nr      = -1
1358!
1359!--                            Determine the grid indices of the particle position
1360                               ip = INT( tmp_particle%x * ddx )
1361                               jp = INT( tmp_particle%y * ddy )
1362!
1363!--                            In case of stretching the actual k index is found iteratively
1364                               IF ( dz_stretch_level .NE. -9999999.9_wp  .OR.           &
1365                                    dz_stretch_level_start(1) .NE. -9999999.9_wp ) THEN
1366                                  kp = MINLOC( ABS( tmp_particle%z - zu ), DIM = 1 ) - 1
1367                               ELSE
1368                                  kp = INT( tmp_particle%z / dz(1) + 1 + offset_ocean_nzt )
1369                               ENDIF
1370!
1371!--                            Determine surface level. Therefore, check for
1372!--                            upward-facing wall on w-grid.
1373                               k_surf = get_topography_top_index_ji( jp, ip, 'w' )
1374                               IF ( seed_follows_topography )  THEN
1375!
1376!--                               Particle height is given relative to topography
1377                                  kp = kp + k_surf
1378                                  tmp_particle%z = tmp_particle%z + zw(k_surf)
1379!--                               Skip particle release if particle position is
1380!--                               above model top, or within topography in case
1381!--                               of overhanging structures.
1382                                  IF ( kp > nzt  .OR.                          &
1383                                 .NOT. BTEST( wall_flags_0(kp,jp,ip), 0 ) )  THEN
1384                                     pos_x = pos_x + pdx(i)
1385                                     CYCLE xloop
1386                                  ENDIF
1387!
1388!--                            Skip particle release if particle position is
1389!--                            below surface, or within topography in case
1390!--                            of overhanging structures.
1391                               ELSEIF ( .NOT. seed_follows_topography .AND.    &
1392                                         tmp_particle%z <= zw(k_surf)  .OR.    &
1393                                        .NOT. BTEST( wall_flags_0(kp,jp,ip), 0 ) )&
1394                               THEN
1395                                  pos_x = pos_x + pdx(i)
1396                                  CYCLE xloop
1397                               ENDIF
1398
1399                               local_count(kp,jp,ip) = local_count(kp,jp,ip) + 1
1400
1401                               IF ( .NOT. first_stride )  THEN
1402                                  IF ( ip < nxl  .OR.  jp < nys  .OR.  kp < nzb+1 )  THEN
1403                                     write(6,*) 'xl ',ip,jp,kp,nxl,nys,nzb+1
1404                                  ENDIF
1405                                  IF ( ip > nxr  .OR.  jp > nyn  .OR.  kp > nzt )  THEN
1406                                     write(6,*) 'xu ',ip,jp,kp,nxr,nyn,nzt
1407                                  ENDIF
1408                                  grid_particles(kp,jp,ip)%particles(local_count(kp,jp,ip)) = tmp_particle
1409                               ENDIF
1410                            ENDDO
1411                         ENDIF
1412                         pos_x = pos_x + pdx(i)
1413                      ENDDO xloop
1414                   ENDIF
1415                   pos_y = pos_y + pdy(i)
1416                ENDDO
1417             ENDIF
1418
1419             pos_z = pos_z + pdz(i)
1420          ENDDO
1421       ENDDO
1422
1423       IF ( first_stride )  THEN
1424          DO  ip = nxl, nxr
1425             DO  jp = nys, nyn
1426                DO  kp = nzb+1, nzt
1427                   IF ( phase == PHASE_INIT )  THEN
1428                      IF ( local_count(kp,jp,ip) > 0 )  THEN
1429                         alloc_size = MAX( INT( local_count(kp,jp,ip) *        &
1430                            ( 1.0_wp + alloc_factor / 100.0_wp ) ),            &
1431                            1 )
1432                      ELSE
1433                         alloc_size = 1
1434                      ENDIF
1435                      ALLOCATE(grid_particles(kp,jp,ip)%particles(1:alloc_size))
1436                      DO  n = 1, alloc_size
1437                         grid_particles(kp,jp,ip)%particles(n) = zero_particle
1438                      ENDDO
1439                   ELSEIF ( phase == PHASE_RELEASE )  THEN
1440                      IF ( local_count(kp,jp,ip) > 0 )  THEN
1441                         new_size   = local_count(kp,jp,ip) + prt_count(kp,jp,ip)
1442                         alloc_size = MAX( INT( new_size * ( 1.0_wp +          &
1443                            alloc_factor / 100.0_wp ) ), 1 )
1444                         IF( alloc_size > SIZE( grid_particles(kp,jp,ip)%particles) )  THEN
1445                            CALL realloc_particles_array(ip,jp,kp,alloc_size)
1446                         ENDIF
1447                      ENDIF
1448                   ENDIF
1449                ENDDO
1450             ENDDO
1451          ENDDO
1452       ENDIF
1453
1454    ENDDO
1455
1456    local_start = prt_count+1
1457    prt_count   = local_count
1458!
1459!-- Calculate particle IDs
1460    DO  ip = nxl, nxr
1461       DO  jp = nys, nyn
1462          DO  kp = nzb+1, nzt
1463             number_of_particles = prt_count(kp,jp,ip)
1464             IF ( number_of_particles <= 0 )  CYCLE
1465             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
1466
1467             DO  n = local_start(kp,jp,ip), number_of_particles  !only new particles
1468
1469                particles(n)%id = 10000_idp**3 * grid_particles(kp,jp,ip)%id_counter + &
1470                                  10000_idp**2 * kp + 10000_idp * jp + ip
1471!
1472!--             Count the number of particles that have been released before
1473                grid_particles(kp,jp,ip)%id_counter =                          &
1474                                         grid_particles(kp,jp,ip)%id_counter + 1
1475
1476             ENDDO
1477
1478          ENDDO
1479       ENDDO
1480    ENDDO
1481!
1482!-- Initialize aerosol background spectrum
1483    IF ( curvature_solution_effects )  THEN
1484       CALL lpm_init_aerosols(local_start)
1485    ENDIF
1486!
1487!-- Add random fluctuation to particle positions.
1488    IF ( random_start_position )  THEN
1489       DO  ip = nxl, nxr
1490          DO  jp = nys, nyn
1491             DO  kp = nzb+1, nzt
1492                number_of_particles = prt_count(kp,jp,ip)
1493                IF ( number_of_particles <= 0 )  CYCLE
1494                particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
1495!
1496!--             Move only new particles. Moreover, limit random fluctuation
1497!--             in order to prevent that particles move more than one grid box,
1498!--             which would lead to problems concerning particle exchange
1499!--             between processors in case pdx/pdy are larger than dx/dy,
1500!--             respectively.
1501                DO  n = local_start(kp,jp,ip), number_of_particles
1502                   IF ( psl(particles(n)%group) /= psr(particles(n)%group) )  THEN
1503                      rand_contr = ( random_function( iran_part ) - 0.5_wp ) * &
1504                                     pdx(particles(n)%group)
1505                      particles(n)%x = particles(n)%x +                        &
1506                              MERGE( rand_contr, SIGN( dx, rand_contr ),       &
1507                                     ABS( rand_contr ) < dx                    &
1508                                   )
1509                   ENDIF
1510                   IF ( pss(particles(n)%group) /= psn(particles(n)%group) )  THEN
1511                      rand_contr = ( random_function( iran_part ) - 0.5_wp ) * &
1512                                     pdy(particles(n)%group)
1513                      particles(n)%y = particles(n)%y +                        &
1514                              MERGE( rand_contr, SIGN( dy, rand_contr ),       &
1515                                     ABS( rand_contr ) < dy                    &
1516                                   )
1517                   ENDIF
1518                   IF ( psb(particles(n)%group) /= pst(particles(n)%group) )  THEN
1519                      rand_contr = ( random_function( iran_part ) - 0.5_wp ) * &
1520                                     pdz(particles(n)%group)
1521                      particles(n)%z = particles(n)%z +                        &
1522                              MERGE( rand_contr, SIGN( dzw(kp), rand_contr ),  &
1523                                     ABS( rand_contr ) < dzw(kp)               &
1524                                   )
1525                   ENDIF
1526                ENDDO
1527!
1528!--             Identify particles located outside the model domain and reflect
1529!--             or absorb them if necessary.
1530                CALL lpm_boundary_conds( 'bottom/top', i, j, k )
1531!
1532!--             Furthermore, remove particles located in topography. Note, as
1533!--             the particle speed is still zero at this point, wall
1534!--             reflection boundary conditions will not work in this case.
1535                particles =>                                                   &
1536                       grid_particles(kp,jp,ip)%particles(1:number_of_particles)
1537                DO  n = local_start(kp,jp,ip), number_of_particles
1538                   i = particles(n)%x * ddx
1539                   j = particles(n)%y * ddy
1540                   k = particles(n)%z / dz(1) + 1 + offset_ocean_nzt
1541                   DO WHILE( zw(k) < particles(n)%z )
1542                      k = k + 1
1543                   ENDDO
1544                   DO WHILE( zw(k-1) > particles(n)%z )
1545                      k = k - 1
1546                   ENDDO
1547!
1548!--                Check if particle is within topography
1549                   IF ( .NOT. BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
1550                      particles(n)%particle_mask = .FALSE.
1551                      deleted_particles = deleted_particles + 1
1552                   ENDIF
1553
1554                ENDDO
1555             ENDDO
1556          ENDDO
1557       ENDDO
1558!
1559!--    Exchange particles between grid cells and processors
1560       CALL lpm_move_particle
1561       CALL lpm_exchange_horiz
1562
1563    ENDIF
1564!
1565!-- In case of random_start_position, delete particles identified by
1566!-- lpm_exchange_horiz and lpm_boundary_conds. Then sort particles into blocks,
1567!-- which is needed for a fast interpolation of the LES fields on the particle
1568!-- position.
1569    CALL lpm_sort_and_delete
1570!
1571!-- Determine the current number of particles
1572    DO  ip = nxl, nxr
1573       DO  jp = nys, nyn
1574          DO  kp = nzb+1, nzt
1575             number_of_particles         = number_of_particles                 &
1576                                           + prt_count(kp,jp,ip)
1577          ENDDO
1578       ENDDO
1579    ENDDO
1580!
1581!-- Calculate the number of particles of the total domain
1582#if defined( __parallel )
1583    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1584    CALL MPI_ALLREDUCE( number_of_particles, total_number_of_particles, 1, &
1585    MPI_INTEGER, MPI_SUM, comm2d, ierr )
1586#else
1587    total_number_of_particles = number_of_particles
1588#endif
1589
1590    RETURN
1591
1592 END SUBROUTINE lpm_create_particle
1593 
1594 
1595!------------------------------------------------------------------------------!
1596! Description:
1597! ------------
1598!> This routine initialize the particles as aerosols with physio-chemical
1599!> properties.
1600!------------------------------------------------------------------------------!   
1601 SUBROUTINE lpm_init_aerosols(local_start)
1602
1603    REAL(wp)  :: afactor            !< curvature effects
1604    REAL(wp)  :: bfactor            !< solute effects
1605    REAL(wp)  :: dlogr              !< logarithmic width of radius bin
1606    REAL(wp)  :: e_a                !< vapor pressure
1607    REAL(wp)  :: e_s                !< saturation vapor pressure
1608    REAL(wp)  :: rmin = 0.005e-6_wp !< minimum aerosol radius
1609    REAL(wp)  :: rmax = 10.0e-6_wp  !< maximum aerosol radius
1610    REAL(wp)  :: r_mid              !< mean radius of bin
1611    REAL(wp)  :: r_l                !< left radius of bin
1612    REAL(wp)  :: r_r                !< right radius of bin
1613    REAL(wp)  :: sigma              !< surface tension
1614    REAL(wp)  :: t_int              !< temperature
1615
1616    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg), INTENT(IN) ::  local_start !<
1617
1618    INTEGER(iwp)  :: n              !<
1619    INTEGER(iwp)  :: ip             !<
1620    INTEGER(iwp)  :: jp             !<
1621    INTEGER(iwp)  :: kp             !<
1622
1623!
1624!-- Set constants for different aerosol species
1625    IF ( TRIM(aero_species) .EQ. 'nacl' ) THEN
1626       molecular_weight_of_solute = 0.05844_wp 
1627       rho_s                      = 2165.0_wp
1628       vanthoff                   = 2.0_wp
1629    ELSEIF ( TRIM(aero_species) .EQ. 'c3h4o4' ) THEN
1630       molecular_weight_of_solute = 0.10406_wp 
1631       rho_s                      = 1600.0_wp
1632       vanthoff                   = 1.37_wp
1633    ELSEIF ( TRIM(aero_species) .EQ. 'nh4o3' ) THEN
1634       molecular_weight_of_solute = 0.08004_wp 
1635       rho_s                      = 1720.0_wp
1636       vanthoff                   = 2.31_wp
1637    ELSE
1638       WRITE( message_string, * ) 'unknown aerosol species ',   &
1639                                'aero_species = "', TRIM( aero_species ), '"'
1640       CALL message( 'lpm_init', 'PA0470', 1, 2, 0, 6, 0 )
1641    ENDIF
1642!
1643!-- The following typical aerosol spectra are taken from Jaenicke (1993):
1644!-- Tropospheric aerosols. Published in Aerosol-Cloud-Climate Interactions.
1645    IF ( TRIM(aero_type) .EQ. 'polar' )  THEN
1646       na        = (/ 2.17e1, 1.86e-1, 3.04e-4 /) * 1.0E6_wp
1647       rm        = (/ 0.0689, 0.375, 4.29 /) * 1.0E-6_wp
1648       log_sigma = (/ 0.245, 0.300, 0.291 /)
1649    ELSEIF ( TRIM(aero_type) .EQ. 'background' )  THEN
1650       na        = (/ 1.29e2, 5.97e1, 6.35e1 /) * 1.0E6_wp
1651       rm        = (/ 0.0036, 0.127, 0.259 /) * 1.0E-6_wp
1652       log_sigma = (/ 0.645, 0.253, 0.425 /)
1653    ELSEIF ( TRIM(aero_type) .EQ. 'maritime' )  THEN
1654       na        = (/ 1.33e2, 6.66e1, 3.06e0 /) * 1.0E6_wp
1655       rm        = (/ 0.0039, 0.133, 0.29 /) * 1.0E-6_wp
1656       log_sigma = (/ 0.657, 0.210, 0.396 /)
1657    ELSEIF ( TRIM(aero_type) .EQ. 'continental' )  THEN
1658       na        = (/ 3.20e3, 2.90e3, 3.00e-1 /) * 1.0E6_wp
1659       rm        = (/ 0.01, 0.058, 0.9 /) * 1.0E-6_wp
1660       log_sigma = (/ 0.161, 0.217, 0.380 /)
1661    ELSEIF ( TRIM(aero_type) .EQ. 'desert' )  THEN
1662       na        = (/ 7.26e2, 1.14e3, 1.78e-1 /) * 1.0E6_wp
1663       rm        = (/ 0.001, 0.0188, 10.8 /) * 1.0E-6_wp
1664       log_sigma = (/ 0.247, 0.770, 0.438 /)
1665    ELSEIF ( TRIM(aero_type) .EQ. 'rural' )  THEN
1666       na        = (/ 6.65e3, 1.47e2, 1.99e3 /) * 1.0E6_wp
1667       rm        = (/ 0.00739, 0.0269, 0.0419 /) * 1.0E-6_wp
1668       log_sigma = (/ 0.225, 0.557, 0.266 /)
1669    ELSEIF ( TRIM(aero_type) .EQ. 'urban' )  THEN
1670       na        = (/ 9.93e4, 1.11e3, 3.64e4 /) * 1.0E6_wp
1671       rm        = (/ 0.00651, 0.00714, 0.0248 /) * 1.0E-6_wp
1672       log_sigma = (/ 0.245, 0.666, 0.337 /)
1673    ELSEIF ( TRIM(aero_type) .EQ. 'user' )  THEN
1674       CONTINUE
1675    ELSE
1676       WRITE( message_string, * ) 'unknown aerosol type ',   &
1677                                'aero_type = "', TRIM( aero_type ), '"'
1678       CALL message( 'lpm_init', 'PA0459', 1, 2, 0, 6, 0 )
1679    ENDIF
1680
1681    DO  ip = nxl, nxr
1682       DO  jp = nys, nyn
1683          DO  kp = nzb+1, nzt
1684
1685             number_of_particles = prt_count(kp,jp,ip)
1686             IF ( number_of_particles <= 0 )  CYCLE
1687             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
1688
1689             dlogr   = ( LOG10(rmax) - LOG10(rmin) ) / ( number_of_particles - local_start(kp,jp,ip) + 1 )
1690!
1691!--          Initialize the aerosols with a predefined spectral distribution
1692!--          of the dry radius (logarithmically increasing bins) and a varying
1693!--          weighting factor
1694             DO  n = local_start(kp,jp,ip), number_of_particles  !only new particles
1695
1696                r_l   = 10.0**( LOG10( rmin ) + (n-1) * dlogr )
1697                r_r   = 10.0**( LOG10( rmin ) + n * dlogr )
1698                r_mid = SQRT( r_l * r_r )
1699
1700                particles(n)%aux1          = r_mid
1701                particles(n)%weight_factor =                                           &
1702                   ( na(1) / ( SQRT( 2.0_wp * pi ) * log_sigma(1) ) *                     &
1703                     EXP( - LOG10( r_mid / rm(1) )**2 / ( 2.0_wp * log_sigma(1)**2 ) ) +  &
1704                     na(2) / ( SQRT( 2.0_wp * pi ) * log_sigma(2) ) *                     &
1705                     EXP( - LOG10( r_mid / rm(2) )**2 / ( 2.0_wp * log_sigma(2)**2 ) ) +  &
1706                     na(3) / ( SQRT( 2.0_wp * pi ) * log_sigma(3) ) *                     &
1707                     EXP( - LOG10( r_mid / rm(3) )**2 / ( 2.0_wp * log_sigma(3)**2 ) )    &
1708                   ) * ( LOG10(r_r) - LOG10(r_l) ) * ( dx * dy * dzw(kp) )
1709
1710!
1711!--             Multiply weight_factor with the namelist parameter aero_weight
1712!--             to increase or decrease the number of simulated aerosols
1713                particles(n)%weight_factor = particles(n)%weight_factor * aero_weight
1714
1715                IF ( particles(n)%weight_factor - FLOOR(particles(n)%weight_factor,KIND=wp) &
1716                     .GT. random_function( iran_part ) )  THEN
1717                   particles(n)%weight_factor = FLOOR(particles(n)%weight_factor,KIND=wp) + 1.0_wp
1718                ELSE
1719                   particles(n)%weight_factor = FLOOR(particles(n)%weight_factor,KIND=wp)
1720                ENDIF
1721!
1722!--             Unnecessary particles will be deleted
1723                IF ( particles(n)%weight_factor .LE. 0.0_wp )  particles(n)%particle_mask = .FALSE.
1724
1725             ENDDO
1726!
1727!--          Set particle radius to equilibrium radius based on the environmental
1728!--          supersaturation (Khvorostyanov and Curry, 2007, JGR). This avoids
1729!--          the sometimes lengthy growth toward their equilibrium radius within
1730!--          the simulation.
1731             t_int  = pt(kp,jp,ip) * exner(kp)
1732
1733             e_s = magnus( t_int )
1734             e_a = q(kp,jp,ip) * hyp(kp) / ( q(kp,jp,ip) + rd_d_rv )
1735
1736             sigma   = 0.0761_wp - 0.000155_wp * ( t_int - 273.15_wp )
1737             afactor = 2.0_wp * sigma / ( rho_l * r_v * t_int )
1738
1739             bfactor = vanthoff * molecular_weight_of_water *    &
1740                       rho_s / ( molecular_weight_of_solute * rho_l )
1741!
1742!--          The formula is only valid for subsaturated environments. For
1743!--          supersaturations higher than -5 %, the supersaturation is set to -5%.
1744             IF ( e_a / e_s >= 0.95_wp )  e_a = 0.95_wp * e_s
1745
1746             DO  n = local_start(kp,jp,ip), number_of_particles  !only new particles
1747!
1748!--             For details on this equation, see Eq. (14) of Khvorostyanov and
1749!--             Curry (2007, JGR)
1750                particles(n)%radius = bfactor**0.3333333_wp *                  &
1751                   particles(n)%aux1 / ( 1.0_wp - e_a / e_s )**0.3333333_wp / &
1752                   ( 1.0_wp + ( afactor / ( 3.0_wp * bfactor**0.3333333_wp *   &
1753                     particles(n)%aux1 ) ) /                                  &
1754                     ( 1.0_wp - e_a / e_s )**0.6666666_wp                      &
1755                   )
1756
1757             ENDDO
1758
1759          ENDDO
1760       ENDDO
1761    ENDDO
1762
1763 END SUBROUTINE lpm_init_aerosols
1764
1765
1766!------------------------------------------------------------------------------!
1767! Description:
1768! ------------
1769!> Calculates quantities required for considering the SGS velocity fluctuations
1770!> in the particle transport by a stochastic approach. The respective
1771!> quantities are: SGS-TKE gradients and horizontally averaged profiles of the
1772!> SGS TKE and the resolved-scale velocity variances.
1773!------------------------------------------------------------------------------!
1774 SUBROUTINE lpm_init_sgs_tke
1775
1776    USE statistics,                                                            &
1777        ONLY:  flow_statistics_called, hom, sums, sums_l
1778
1779    INTEGER(iwp) ::  i      !< index variable along x
1780    INTEGER(iwp) ::  j      !< index variable along y
1781    INTEGER(iwp) ::  k      !< index variable along z
1782    INTEGER(iwp) ::  m      !< running index for the surface elements
1783
1784    REAL(wp) ::  flag1      !< flag to mask topography
1785
1786!
1787!-- TKE gradient along x and y
1788    DO  i = nxl, nxr
1789       DO  j = nys, nyn
1790          DO  k = nzb, nzt+1
1791
1792             IF ( .NOT. BTEST( wall_flags_0(k,j,i-1), 0 )  .AND.               &
1793                        BTEST( wall_flags_0(k,j,i), 0   )  .AND.               &
1794                        BTEST( wall_flags_0(k,j,i+1), 0 ) )                    &
1795             THEN
1796                de_dx(k,j,i) = 2.0_wp * sgs_wf_part *                          &
1797                               ( e(k,j,i+1) - e(k,j,i) ) * ddx
1798             ELSEIF ( BTEST( wall_flags_0(k,j,i-1), 0 )  .AND.                 &
1799                      BTEST( wall_flags_0(k,j,i), 0   )  .AND.                 &
1800                .NOT. BTEST( wall_flags_0(k,j,i+1), 0 ) )                      &
1801             THEN
1802                de_dx(k,j,i) = 2.0_wp * sgs_wf_part *                          &
1803                               ( e(k,j,i) - e(k,j,i-1) ) * ddx
1804             ELSEIF ( .NOT. BTEST( wall_flags_0(k,j,i), 22   )  .AND.          &
1805                      .NOT. BTEST( wall_flags_0(k,j,i+1), 22 ) )               &   
1806             THEN
1807                de_dx(k,j,i) = 0.0_wp
1808             ELSEIF ( .NOT. BTEST( wall_flags_0(k,j,i-1), 22 )  .AND.          &
1809                      .NOT. BTEST( wall_flags_0(k,j,i), 22   ) )               &
1810             THEN
1811                de_dx(k,j,i) = 0.0_wp
1812             ELSE
1813                de_dx(k,j,i) = sgs_wf_part * ( e(k,j,i+1) - e(k,j,i-1) ) * ddx
1814             ENDIF
1815
1816             IF ( .NOT. BTEST( wall_flags_0(k,j-1,i), 0 )  .AND.               &
1817                        BTEST( wall_flags_0(k,j,i), 0   )  .AND.               &
1818                        BTEST( wall_flags_0(k,j+1,i), 0 ) )                    &
1819             THEN
1820                de_dy(k,j,i) = 2.0_wp * sgs_wf_part *                          &
1821                               ( e(k,j+1,i) - e(k,j,i) ) * ddy
1822             ELSEIF ( BTEST( wall_flags_0(k,j-1,i), 0 )  .AND.                 &
1823                      BTEST( wall_flags_0(k,j,i), 0   )  .AND.                 &
1824                .NOT. BTEST( wall_flags_0(k,j+1,i), 0 ) )                      &
1825             THEN
1826                de_dy(k,j,i) = 2.0_wp * sgs_wf_part *                          &
1827                               ( e(k,j,i) - e(k,j-1,i) ) * ddy
1828             ELSEIF ( .NOT. BTEST( wall_flags_0(k,j,i), 22   )  .AND.          &
1829                      .NOT. BTEST( wall_flags_0(k,j+1,i), 22 ) )               &   
1830             THEN
1831                de_dy(k,j,i) = 0.0_wp
1832             ELSEIF ( .NOT. BTEST( wall_flags_0(k,j-1,i), 22 )  .AND.          &
1833                      .NOT. BTEST( wall_flags_0(k,j,i), 22   ) )               &
1834             THEN
1835                de_dy(k,j,i) = 0.0_wp
1836             ELSE
1837                de_dy(k,j,i) = sgs_wf_part * ( e(k,j+1,i) - e(k,j-1,i) ) * ddy
1838             ENDIF
1839
1840          ENDDO
1841       ENDDO
1842    ENDDO
1843
1844!
1845!-- TKE gradient along z at topograhy and  including bottom and top boundary conditions
1846    DO  i = nxl, nxr
1847       DO  j = nys, nyn
1848          DO  k = nzb+1, nzt-1
1849!
1850!--          Flag to mask topography
1851             flag1 = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0  ) )
1852
1853             de_dz(k,j,i) = 2.0_wp * sgs_wf_part *                             &
1854                           ( e(k+1,j,i) - e(k-1,j,i) ) / ( zu(k+1) - zu(k-1) ) &
1855                                                 * flag1 
1856          ENDDO
1857!
1858!--       upward-facing surfaces
1859          DO  m = bc_h(0)%start_index(j,i), bc_h(0)%end_index(j,i)
1860             k            = bc_h(0)%k(m)
1861             de_dz(k,j,i) = 2.0_wp * sgs_wf_part *                             &
1862                           ( e(k+1,j,i) - e(k,j,i)   ) / ( zu(k+1) - zu(k) )
1863          ENDDO
1864!
1865!--       downward-facing surfaces
1866          DO  m = bc_h(1)%start_index(j,i), bc_h(1)%end_index(j,i)
1867             k            = bc_h(1)%k(m)
1868             de_dz(k,j,i) = 2.0_wp * sgs_wf_part *                             &
1869                           ( e(k,j,i) - e(k-1,j,i)   ) / ( zu(k) - zu(k-1) )
1870          ENDDO
1871
1872          de_dz(nzb,j,i)   = 0.0_wp
1873          de_dz(nzt,j,i)   = 0.0_wp
1874          de_dz(nzt+1,j,i) = 0.0_wp
1875       ENDDO
1876    ENDDO
1877!
1878!-- Ghost point exchange
1879    CALL exchange_horiz( de_dx, nbgp )
1880    CALL exchange_horiz( de_dy, nbgp )
1881    CALL exchange_horiz( de_dz, nbgp )
1882    CALL exchange_horiz( diss, nbgp  )
1883!
1884!-- Set boundary conditions at non-periodic boundaries. Note, at non-period
1885!-- boundaries zero-gradient boundary conditions are set for the subgrid TKE.
1886!-- Thus, TKE gradients normal to the respective lateral boundaries are zero,
1887!-- while tangetial TKE gradients then must be the same as within the prognostic
1888!-- domain. 
1889    IF ( bc_dirichlet_l )  THEN
1890       de_dx(:,:,-1) = 0.0_wp
1891       de_dy(:,:,-1) = de_dy(:,:,0) 
1892       de_dz(:,:,-1) = de_dz(:,:,0)
1893    ENDIF
1894    IF ( bc_dirichlet_r )  THEN
1895       de_dx(:,:,nxr+1) = 0.0_wp
1896       de_dy(:,:,nxr+1) = de_dy(:,:,nxr) 
1897       de_dz(:,:,nxr+1) = de_dz(:,:,nxr)
1898    ENDIF
1899    IF ( bc_dirichlet_n )  THEN
1900       de_dx(:,nyn+1,:) = de_dx(:,nyn,:)
1901       de_dy(:,nyn+1,:) = 0.0_wp 
1902       de_dz(:,nyn+1,:) = de_dz(:,nyn,:)
1903    ENDIF
1904    IF ( bc_dirichlet_s )  THEN
1905       de_dx(:,nys-1,:) = de_dx(:,nys,:)
1906       de_dy(:,nys-1,:) = 0.0_wp 
1907       de_dz(:,nys-1,:) = de_dz(:,nys,:)
1908    ENDIF 
1909!
1910!-- Calculate the horizontally averaged profiles of SGS TKE and resolved
1911!-- velocity variances (they may have been already calculated in routine
1912!-- flow_statistics).
1913    IF ( .NOT. flow_statistics_called )  THEN
1914
1915!
1916!--    First calculate horizontally averaged profiles of the horizontal
1917!--    velocities.
1918       sums_l(:,1,0) = 0.0_wp
1919       sums_l(:,2,0) = 0.0_wp
1920
1921       DO  i = nxl, nxr
1922          DO  j =  nys, nyn
1923             DO  k = nzb, nzt+1
1924!
1925!--             Flag indicating vicinity of wall
1926                flag1 = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 24 ) )
1927
1928                sums_l(k,1,0)  = sums_l(k,1,0)  + u(k,j,i) * flag1
1929                sums_l(k,2,0)  = sums_l(k,2,0)  + v(k,j,i) * flag1
1930             ENDDO
1931          ENDDO
1932       ENDDO
1933
1934#if defined( __parallel )
1935!
1936!--    Compute total sum from local sums
1937       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1938       CALL MPI_ALLREDUCE( sums_l(nzb,1,0), sums(nzb,1), nzt+2-nzb, &
1939                           MPI_REAL, MPI_SUM, comm2d, ierr )
1940       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1941       CALL MPI_ALLREDUCE( sums_l(nzb,2,0), sums(nzb,2), nzt+2-nzb, &
1942                              MPI_REAL, MPI_SUM, comm2d, ierr )
1943#else
1944       sums(:,1) = sums_l(:,1,0)
1945       sums(:,2) = sums_l(:,2,0)
1946#endif
1947
1948!
1949!--    Final values are obtained by division by the total number of grid
1950!--    points used for the summation.
1951       hom(:,1,1,0) = sums(:,1) / ngp_2dh_outer(:,0)   ! u
1952       hom(:,1,2,0) = sums(:,2) / ngp_2dh_outer(:,0)   ! v
1953
1954!
1955!--    Now calculate the profiles of SGS TKE and the resolved-scale
1956!--    velocity variances
1957       sums_l(:,8,0)  = 0.0_wp
1958       sums_l(:,30,0) = 0.0_wp
1959       sums_l(:,31,0) = 0.0_wp
1960       sums_l(:,32,0) = 0.0_wp
1961       DO  i = nxl, nxr
1962          DO  j = nys, nyn
1963             DO  k = nzb, nzt+1
1964!
1965!--             Flag indicating vicinity of wall
1966                flag1 = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 24 ) )
1967
1968                sums_l(k,8,0)  = sums_l(k,8,0)  + e(k,j,i)                       * flag1
1969                sums_l(k,30,0) = sums_l(k,30,0) + ( u(k,j,i) - hom(k,1,1,0) )**2 * flag1
1970                sums_l(k,31,0) = sums_l(k,31,0) + ( v(k,j,i) - hom(k,1,2,0) )**2 * flag1
1971                sums_l(k,32,0) = sums_l(k,32,0) + w(k,j,i)**2                    * flag1
1972             ENDDO
1973          ENDDO
1974       ENDDO
1975
1976#if defined( __parallel )
1977!
1978!--    Compute total sum from local sums
1979       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1980       CALL MPI_ALLREDUCE( sums_l(nzb,8,0), sums(nzb,8), nzt+2-nzb, &
1981                           MPI_REAL, MPI_SUM, comm2d, ierr )
1982       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1983       CALL MPI_ALLREDUCE( sums_l(nzb,30,0), sums(nzb,30), nzt+2-nzb, &
1984                           MPI_REAL, MPI_SUM, comm2d, ierr )
1985       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1986       CALL MPI_ALLREDUCE( sums_l(nzb,31,0), sums(nzb,31), nzt+2-nzb, &
1987                           MPI_REAL, MPI_SUM, comm2d, ierr )
1988       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1989       CALL MPI_ALLREDUCE( sums_l(nzb,32,0), sums(nzb,32), nzt+2-nzb, &
1990                           MPI_REAL, MPI_SUM, comm2d, ierr )
1991
1992#else
1993       sums(:,8)  = sums_l(:,8,0)
1994       sums(:,30) = sums_l(:,30,0)
1995       sums(:,31) = sums_l(:,31,0)
1996       sums(:,32) = sums_l(:,32,0)
1997#endif
1998
1999!
2000!--    Final values are obtained by division by the total number of grid
2001!--    points used for the summation.
2002       hom(:,1,8,0)  = sums(:,8)  / ngp_2dh_outer(:,0)   ! e
2003       hom(:,1,30,0) = sums(:,30) / ngp_2dh_outer(:,0)   ! u*2
2004       hom(:,1,31,0) = sums(:,31) / ngp_2dh_outer(:,0)   ! v*2
2005       hom(:,1,32,0) = sums(:,32) / ngp_2dh_outer(:,0)   ! w*2
2006
2007    ENDIF
2008
2009 END SUBROUTINE lpm_init_sgs_tke
2010 
2011 
2012!------------------------------------------------------------------------------!
2013! Description:
2014! ------------
2015!> Sobroutine control lpm actions, i.e. all actions during one time step.
2016!------------------------------------------------------------------------------! 
2017 SUBROUTINE lpm_actions( location )
2018
2019    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
2020
2021    INTEGER(iwp)       ::  i                  !<
2022    INTEGER(iwp)       ::  ie                 !<
2023    INTEGER(iwp)       ::  is                 !<
2024    INTEGER(iwp)       ::  j                  !<
2025    INTEGER(iwp)       ::  je                 !<
2026    INTEGER(iwp)       ::  js                 !<
2027    INTEGER(iwp), SAVE ::  lpm_count = 0      !<
2028    INTEGER(iwp)       ::  k                  !<
2029    INTEGER(iwp)       ::  ke                 !<
2030    INTEGER(iwp)       ::  ks                 !<
2031    INTEGER(iwp)       ::  m                  !<
2032    INTEGER(iwp), SAVE ::  steps = 0          !<
2033
2034    LOGICAL            ::  first_loop_stride  !<
2035
2036
2037    SELECT CASE ( location )
2038
2039       CASE ( 'after_prognostic_equations' )
2040
2041          CALL cpu_log( log_point(25), 'lpm', 'start' )
2042!
2043!--       Write particle data at current time on file.
2044!--       This has to be done here, before particles are further processed,
2045!--       because they may be deleted within this timestep (in case that
2046!--       dt_write_particle_data = dt_prel = particle_maximum_age).
2047          time_write_particle_data = time_write_particle_data + dt_3d
2048          IF ( time_write_particle_data >= dt_write_particle_data )  THEN
2049
2050             CALL lpm_data_output_particles
2051!
2052!--       The MOD function allows for changes in the output interval with restart
2053!--       runs.
2054             time_write_particle_data = MOD( time_write_particle_data, &
2055                                        MAX( dt_write_particle_data, dt_3d ) )
2056          ENDIF
2057
2058!
2059!--       Initialize arrays for marking those particles to be deleted after the
2060!--       (sub-) timestep
2061          deleted_particles = 0
2062
2063!
2064!--       Initialize variables used for accumulating the number of particles
2065!--       xchanged between the subdomains during all sub-timesteps (if sgs
2066!--       velocities are included). These data are output further below on the
2067!--       particle statistics file.
2068          trlp_count_sum      = 0
2069          trlp_count_recv_sum = 0
2070          trrp_count_sum      = 0
2071          trrp_count_recv_sum = 0
2072          trsp_count_sum      = 0
2073          trsp_count_recv_sum = 0
2074          trnp_count_sum      = 0
2075          trnp_count_recv_sum = 0
2076!
2077!--       Calculate exponential term used in case of particle inertia for each
2078!--       of the particle groups
2079          DO  m = 1, number_of_particle_groups
2080             IF ( particle_groups(m)%density_ratio /= 0.0_wp )  THEN
2081                particle_groups(m)%exp_arg  =                                        &
2082                          4.5_wp * particle_groups(m)%density_ratio *                &
2083                          molecular_viscosity / ( particle_groups(m)%radius )**2
2084
2085                particle_groups(m)%exp_term = EXP( -particle_groups(m)%exp_arg *     &
2086                          dt_3d )
2087             ENDIF
2088          ENDDO
2089!
2090!--       If necessary, release new set of particles
2091          IF ( ( simulated_time - last_particle_release_time ) >= dt_prel  .AND. end_time_prel > simulated_time ) &
2092          THEN
2093             DO WHILE ( ( simulated_time - last_particle_release_time ) >= dt_prel )
2094                CALL lpm_create_particle( PHASE_RELEASE )
2095                last_particle_release_time = last_particle_release_time + dt_prel
2096             ENDDO
2097          ENDIF
2098!
2099!--       Reset summation arrays
2100          IF ( cloud_droplets )  THEN
2101             ql_c  = 0.0_wp
2102             ql_v  = 0.0_wp
2103             ql_vp = 0.0_wp
2104          ENDIF
2105
2106          first_loop_stride = .TRUE.
2107          grid_particles(:,:,:)%time_loop_done = .TRUE.
2108!
2109!--       Timestep loop for particle advection.
2110!--       This loop has to be repeated until the advection time of every particle
2111!--       (within the total domain!) has reached the LES timestep (dt_3d).
2112!--       In case of including the SGS velocities, the particle timestep may be
2113!--       smaller than the LES timestep (because of the Lagrangian timescale
2114!--       restriction) and particles may require to undergo several particle
2115!--       timesteps, before the LES timestep is reached. Because the number of these
2116!--       particle timesteps to be carried out is unknown at first, these steps are
2117!--       carried out in the following infinite loop with exit condition.
2118          DO
2119             CALL cpu_log( log_point_s(44), 'lpm_advec', 'start' )
2120             CALL cpu_log( log_point_s(44), 'lpm_advec', 'pause' )
2121
2122!
2123!--          If particle advection includes SGS velocity components, calculate the
2124!--          required SGS quantities (i.e. gradients of the TKE, as well as
2125!--          horizontally averaged profiles of the SGS TKE and the resolved-scale
2126!--          velocity variances)
2127             IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets )  THEN
2128                CALL lpm_init_sgs_tke
2129             ENDIF
2130!
2131!--          In case SGS-particle speed is considered, particles may carry out
2132!--          several particle timesteps. In order to prevent unnecessary
2133!--          treatment of particles that already reached the final time level,
2134!--          particles are sorted into contiguous blocks of finished and
2135!--          not-finished particles, in addition to their already sorting
2136!--          according to their sub-boxes.
2137             IF ( .NOT. first_loop_stride  .AND.  use_sgs_for_particles )            &
2138                CALL lpm_sort_timeloop_done
2139             DO  i = nxl, nxr
2140                DO  j = nys, nyn
2141                   DO  k = nzb+1, nzt
2142
2143                      number_of_particles = prt_count(k,j,i)
2144!
2145!--                   If grid cell gets empty, flag must be true
2146                      IF ( number_of_particles <= 0 )  THEN
2147                         grid_particles(k,j,i)%time_loop_done = .TRUE.
2148                         CYCLE
2149                      ENDIF
2150
2151                      IF ( .NOT. first_loop_stride  .AND.  &
2152                           grid_particles(k,j,i)%time_loop_done ) CYCLE
2153
2154                      particles => grid_particles(k,j,i)%particles(1:number_of_particles)
2155
2156                      particles(1:number_of_particles)%particle_mask = .TRUE.
2157!
2158!--                   Initialize the variable storing the total time that a particle
2159!--                   has advanced within the timestep procedure
2160                      IF ( first_loop_stride )  THEN
2161                         particles(1:number_of_particles)%dt_sum = 0.0_wp
2162                      ENDIF
2163!
2164!--                   Particle (droplet) growth by condensation/evaporation and
2165!--                   collision
2166                      IF ( cloud_droplets  .AND.  first_loop_stride)  THEN
2167!
2168!--                      Droplet growth by condensation / evaporation
2169                         CALL lpm_droplet_condensation(i,j,k)
2170!
2171!--                      Particle growth by collision
2172                         IF ( collision_kernel /= 'none' )  THEN
2173                            CALL lpm_droplet_collision(i,j,k)
2174                         ENDIF
2175
2176                      ENDIF
2177!
2178!--                   Initialize the switch used for the loop exit condition checked
2179!--                   at the end of this loop. If at least one particle has failed to
2180!--                   reach the LES timestep, this switch will be set false in
2181!--                   lpm_advec.
2182                      dt_3d_reached_l = .TRUE.
2183
2184!
2185!--                   Particle advection
2186                      CALL lpm_advec(TRIM(particle_interpolation),i,j,k)
2187!
2188!--                   Particle reflection from walls. Only applied if the particles
2189!--                   are in the vertical range of the topography. (Here, some
2190!--                   optimization is still possible.)
2191                      IF ( topography /= 'flat' .AND. k < nzb_max + 2 )  THEN
2192                         CALL  lpm_boundary_conds( 'walls', i, j, k )
2193                      ENDIF
2194!
2195!--                   User-defined actions after the calculation of the new particle
2196!--                   position
2197                      CALL user_lpm_advec(i,j,k)
2198!
2199!--                   Apply boundary conditions to those particles that have crossed
2200!--                   the top or bottom boundary and delete those particles, which are
2201!--                   older than allowed
2202                      CALL lpm_boundary_conds( 'bottom/top', i, j, k )
2203!
2204!---                  If not all particles of the actual grid cell have reached the
2205!--                   LES timestep, this cell has to do another loop iteration. Due to
2206!--                   the fact that particles can move into neighboring grid cells,
2207!--                   these neighbor cells also have to perform another loop iteration.
2208!--                   Please note, this realization does not work properly if
2209!--                   particles move into another subdomain.
2210                      IF ( .NOT. dt_3d_reached_l )  THEN
2211                         ks = MAX(nzb+1,k-1)
2212                         ke = MIN(nzt,k+1)
2213                         js = MAX(nys,j-1)
2214                         je = MIN(nyn,j+1)
2215                         is = MAX(nxl,i-1)
2216                         ie = MIN(nxr,i+1)
2217                         grid_particles(ks:ke,js:je,is:ie)%time_loop_done = .FALSE.
2218                      ELSE
2219                         grid_particles(k,j,i)%time_loop_done = .TRUE.
2220                      ENDIF
2221
2222                   ENDDO
2223                ENDDO
2224             ENDDO
2225             steps = steps + 1
2226             dt_3d_reached_l = ALL(grid_particles(:,:,:)%time_loop_done)
2227!
2228!--          Find out, if all particles on every PE have completed the LES timestep
2229!--          and set the switch corespondingly
2230#if defined( __parallel )
2231             IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
2232             CALL MPI_ALLREDUCE( dt_3d_reached_l, dt_3d_reached, 1, MPI_LOGICAL, &
2233                                 MPI_LAND, comm2d, ierr )
2234#else
2235             dt_3d_reached = dt_3d_reached_l
2236#endif
2237             CALL cpu_log( log_point_s(44), 'lpm_advec', 'stop' )
2238
2239!
2240!--          Apply splitting and merging algorithm
2241             IF ( cloud_droplets )  THEN
2242                IF ( splitting ) THEN
2243                   CALL lpm_splitting
2244                ENDIF
2245                IF ( merging ) THEN
2246                   CALL lpm_merging
2247                ENDIF
2248             ENDIF
2249!
2250!--          Move Particles local to PE to a different grid cell
2251             CALL lpm_move_particle
2252!
2253!--          Horizontal boundary conditions including exchange between subdmains
2254             CALL lpm_exchange_horiz
2255
2256!
2257!--          IF .FALSE., lpm_sort_and_delete is done inside pcmp
2258             IF ( .NOT. dt_3d_reached .OR. .NOT. nested_run )   THEN   
2259!
2260!--             Pack particles (eliminate those marked for deletion),
2261!--             determine new number of particles
2262                CALL lpm_sort_and_delete
2263
2264!--             Initialize variables for the next (sub-) timestep, i.e., for marking
2265!--             those particles to be deleted after the timestep
2266                deleted_particles = 0
2267             ENDIF
2268
2269             IF ( dt_3d_reached )  EXIT
2270
2271             first_loop_stride = .FALSE.
2272          ENDDO   ! timestep loop
2273!
2274!--       in case of nested runs do the transfer of particles after every full model time step
2275          IF ( nested_run )   THEN
2276             CALL particles_from_parent_to_child
2277             CALL particles_from_child_to_parent
2278             CALL pmcp_p_delete_particles_in_fine_grid_area
2279
2280             CALL lpm_sort_and_delete
2281
2282             deleted_particles = 0
2283          ENDIF
2284
2285!
2286!--       Calculate the new liquid water content for each grid box
2287          IF ( cloud_droplets )  CALL lpm_calc_liquid_water_content
2288
2289!
2290!--       Deallocate unused memory
2291          IF ( deallocate_memory  .AND.  lpm_count == step_dealloc )  THEN
2292             CALL dealloc_particles_array
2293             lpm_count = 0
2294          ELSEIF ( deallocate_memory )  THEN
2295             lpm_count = lpm_count + 1
2296          ENDIF
2297
2298!
2299!--       Write particle statistics (in particular the number of particles
2300!--       exchanged between the subdomains) on file
2301          IF ( write_particle_statistics )  CALL lpm_write_exchange_statistics
2302
2303          CALL cpu_log( log_point(25), 'lpm', 'stop' )
2304
2305! !
2306! !--       Output of particle time series
2307!           IF ( particle_advection )  THEN
2308!              IF ( time_dopts >= dt_dopts  .OR.                                                        &
2309!                   ( time_since_reference_point >= particle_advection_start  .AND.                     &
2310!                    first_call_lpm ) )  THEN
2311!                 CALL lpm_data_output_ptseries
2312!                 time_dopts = MOD( time_dopts, MAX( dt_dopts, dt_3d ) )
2313!              ENDIF
2314!           ENDIF
2315
2316       CASE DEFAULT
2317          CONTINUE
2318
2319    END SELECT
2320
2321 END SUBROUTINE lpm_actions
2322 
2323 
2324!------------------------------------------------------------------------------!
2325! Description:
2326! ------------
2327!
2328!------------------------------------------------------------------------------!
2329 SUBROUTINE particles_from_parent_to_child
2330    IMPLICIT NONE
2331
2332    CALL pmcp_c_get_particle_from_parent                         ! Child actions
2333    CALL pmcp_p_fill_particle_win                                ! Parent actions
2334
2335    RETURN
2336 END SUBROUTINE particles_from_parent_to_child
2337
2338 
2339!------------------------------------------------------------------------------!
2340! Description:
2341! ------------
2342!
2343!------------------------------------------------------------------------------!
2344 SUBROUTINE particles_from_child_to_parent
2345    IMPLICIT NONE
2346
2347    CALL pmcp_c_send_particle_to_parent                         ! Child actions
2348    CALL pmcp_p_empty_particle_win                              ! Parent actions
2349
2350    RETURN
2351 END SUBROUTINE particles_from_child_to_parent
2352 
2353!------------------------------------------------------------------------------!
2354! Description:
2355! ------------
2356!> This routine write exchange statistics of the lpm in a ascii file.
2357!------------------------------------------------------------------------------!
2358 SUBROUTINE lpm_write_exchange_statistics
2359
2360    INTEGER(iwp) :: ip         !<
2361    INTEGER(iwp) :: jp         !<
2362    INTEGER(iwp) :: kp         !<
2363    INTEGER(iwp) :: tot_number_of_particles
2364
2365!
2366!-- Determine the current number of particles
2367    number_of_particles         = 0
2368    DO  ip = nxl, nxr
2369       DO  jp = nys, nyn
2370          DO  kp = nzb+1, nzt
2371             number_of_particles = number_of_particles                         &
2372                                     + prt_count(kp,jp,ip)
2373          ENDDO
2374       ENDDO
2375    ENDDO
2376
2377    CALL check_open( 80 )
2378#if defined( __parallel )
2379    WRITE ( 80, 8000 )  current_timestep_number+1, simulated_time+dt_3d, &
2380                        number_of_particles, pleft, trlp_count_sum,      &
2381                        trlp_count_recv_sum, pright, trrp_count_sum,     &
2382                        trrp_count_recv_sum, psouth, trsp_count_sum,     &
2383                        trsp_count_recv_sum, pnorth, trnp_count_sum,     &
2384                        trnp_count_recv_sum
2385#else
2386    WRITE ( 80, 8000 )  current_timestep_number+1, simulated_time+dt_3d, &
2387                        number_of_particles
2388#endif
2389    CALL close_file( 80 )
2390
2391    IF ( number_of_particles > 0 ) THEN
2392        WRITE(9,*) 'number_of_particles ', number_of_particles,                &
2393                    current_timestep_number + 1, simulated_time + dt_3d
2394    ENDIF
2395
2396#if defined( __parallel )
2397    CALL MPI_ALLREDUCE( number_of_particles, tot_number_of_particles, 1,       &
2398                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
2399#else
2400    tot_number_of_particles = number_of_particles
2401#endif
2402
2403    IF ( nested_run )  THEN
2404       CALL pmcp_g_print_number_of_particles( simulated_time+dt_3d,            &
2405                                              tot_number_of_particles)
2406    ENDIF
2407
2408!
2409!-- Formats
24108000 FORMAT (I6,1X,F7.2,4X,I10,5X,4(I3,1X,I4,'/',I4,2X),6X,I10)
2411
2412
2413 END SUBROUTINE lpm_write_exchange_statistics
2414 
2415
2416!------------------------------------------------------------------------------!
2417! Description:
2418! ------------
2419!> Write particle data in FORTRAN binary and/or netCDF format
2420!------------------------------------------------------------------------------!
2421 SUBROUTINE lpm_data_output_particles
2422 
2423    INTEGER(iwp) ::  ip !<
2424    INTEGER(iwp) ::  jp !<
2425    INTEGER(iwp) ::  kp !<
2426
2427    CALL cpu_log( log_point_s(40), 'lpm_data_output', 'start' )
2428
2429!
2430!-- Attention: change version number for unit 85 (in routine check_open)
2431!--            whenever the output format for this unit is changed!
2432    CALL check_open( 85 )
2433
2434    WRITE ( 85 )  simulated_time
2435    WRITE ( 85 )  prt_count
2436         
2437    DO  ip = nxl, nxr
2438       DO  jp = nys, nyn
2439          DO  kp = nzb+1, nzt
2440             number_of_particles = prt_count(kp,jp,ip)
2441             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
2442             IF ( number_of_particles <= 0 )  CYCLE
2443             WRITE ( 85 )  particles
2444          ENDDO
2445       ENDDO
2446    ENDDO
2447
2448    CALL close_file( 85 )
2449
2450
2451#if defined( __netcdf )
2452! !
2453! !-- Output in netCDF format
2454!     CALL check_open( 108 )
2455!
2456! !
2457! !-- Update the NetCDF time axis
2458!     prt_time_count = prt_time_count + 1
2459!
2460!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_time_prt, &
2461!                             (/ simulated_time /),        &
2462!                             start = (/ prt_time_count /), count = (/ 1 /) )
2463!     CALL netcdf_handle_error( 'lpm_data_output_particles', 1 )
2464!
2465! !
2466! !-- Output the real number of particles used
2467!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_rnop_prt, &
2468!                             (/ number_of_particles /),   &
2469!                             start = (/ prt_time_count /), count = (/ 1 /) )
2470!     CALL netcdf_handle_error( 'lpm_data_output_particles', 2 )
2471!
2472! !
2473! !-- Output all particle attributes
2474!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(1), particles%age,      &
2475!                             start = (/ 1, prt_time_count /),               &
2476!                             count = (/ maximum_number_of_particles /) )
2477!     CALL netcdf_handle_error( 'lpm_data_output_particles', 3 )
2478!
2479!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(2), particles%user,     &
2480!                             start = (/ 1, prt_time_count /),               &
2481!                             count = (/ maximum_number_of_particles /) )
2482!     CALL netcdf_handle_error( 'lpm_data_output_particles', 4 )
2483!
2484!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(3), particles%origin_x, &
2485!                             start = (/ 1, prt_time_count /),               &
2486!                             count = (/ maximum_number_of_particles /) )
2487!     CALL netcdf_handle_error( 'lpm_data_output_particles', 5 )
2488!
2489!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(4), particles%origin_y, &
2490!                             start = (/ 1, prt_time_count /),               &
2491!                             count = (/ maximum_number_of_particles /) )
2492!     CALL netcdf_handle_error( 'lpm_data_output_particles', 6 )
2493!
2494!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(5), particles%origin_z, &
2495!                             start = (/ 1, prt_time_count /),               &
2496!                             count = (/ maximum_number_of_particles /) )
2497!     CALL netcdf_handle_error( 'lpm_data_output_particles', 7 )
2498!
2499!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(6), particles%radius,   &
2500!                             start = (/ 1, prt_time_count /),               &
2501!                             count = (/ maximum_number_of_particles /) )
2502!     CALL netcdf_handle_error( 'lpm_data_output_particles', 8 )
2503!
2504!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(7), particles%speed_x,  &
2505!                             start = (/ 1, prt_time_count /),               &
2506!                             count = (/ maximum_number_of_particles /) )
2507!     CALL netcdf_handle_error( 'lpm_data_output_particles', 9 )
2508!
2509!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(8), particles%speed_y,  &
2510!                             start = (/ 1, prt_time_count /),               &
2511!                             count = (/ maximum_number_of_particles /) )
2512!     CALL netcdf_handle_error( 'lpm_data_output_particles', 10 )
2513!
2514!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(9), particles%speed_z,  &
2515!                             start = (/ 1, prt_time_count /),               &
2516!                             count = (/ maximum_number_of_particles /) )
2517!     CALL netcdf_handle_error( 'lpm_data_output_particles', 11 )
2518!
2519!     nc_stat = NF90_PUT_VAR( id_set_prt,id_var_prt(10),                     &
2520!                             particles%weight_factor,                       &
2521!                             start = (/ 1, prt_time_count /),               &
2522!                             count = (/ maximum_number_of_particles /) )
2523!     CALL netcdf_handle_error( 'lpm_data_output_particles', 12 )
2524!
2525!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(11), particles%x,       &
2526!                             start = (/ 1, prt_time_count /),               &
2527!                             count = (/ maximum_number_of_particles /) )
2528!     CALL netcdf_handle_error( 'lpm_data_output_particles', 13 )
2529!
2530!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(12), particles%y,       &
2531!                             start = (/ 1, prt_time_count /),               &
2532!                             count = (/ maximum_number_of_particles /) )
2533!     CALL netcdf_handle_error( 'lpm_data_output_particles', 14 )
2534!
2535!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(13), particles%z,       &
2536!                             start = (/ 1, prt_time_count /),               &
2537!                             count = (/ maximum_number_of_particles /) )
2538!     CALL netcdf_handle_error( 'lpm_data_output_particles', 15 )
2539!
2540!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(14), particles%class,   &
2541!                             start = (/ 1, prt_time_count /),               &
2542!                             count = (/ maximum_number_of_particles /) )
2543!     CALL netcdf_handle_error( 'lpm_data_output_particles', 16 )
2544!
2545!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(15), particles%group,   &
2546!                             start = (/ 1, prt_time_count /),               &
2547!                             count = (/ maximum_number_of_particles /) )
2548!     CALL netcdf_handle_error( 'lpm_data_output_particles', 17 )
2549!
2550!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(16),                    &
2551!                             particles%id2,                                 &
2552!                             start = (/ 1, prt_time_count /),               &
2553!                             count = (/ maximum_number_of_particles /) )
2554!     CALL netcdf_handle_error( 'lpm_data_output_particles', 18 )
2555!
2556!     nc_stat = NF90_PUT_VAR( id_set_prt, id_var_prt(17), particles%id1,     &
2557!                             start = (/ 1, prt_time_count /),               &
2558!                             count = (/ maximum_number_of_particles /) )
2559!     CALL netcdf_handle_error( 'lpm_data_output_particles', 19 )
2560!
2561#endif
2562
2563    CALL cpu_log( log_point_s(40), 'lpm_data_output', 'stop' )
2564
2565 END SUBROUTINE lpm_data_output_particles
2566 
2567!------------------------------------------------------------------------------!
2568! Description:
2569! ------------
2570!> This routine calculates and provide particle timeseries output.
2571!------------------------------------------------------------------------------!
2572 SUBROUTINE lpm_data_output_ptseries
2573 
2574    INTEGER(iwp) ::  i    !<
2575    INTEGER(iwp) ::  inum !<
2576    INTEGER(iwp) ::  j    !<
2577    INTEGER(iwp) ::  jg   !<
2578    INTEGER(iwp) ::  k    !<
2579    INTEGER(iwp) ::  n    !<
2580
2581    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pts_value   !<
2582    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pts_value_l !<
2583
2584
2585    CALL cpu_log( log_point(36), 'data_output_ptseries', 'start' )
2586
2587    IF ( myid == 0 )  THEN
2588!
2589!--    Open file for time series output in NetCDF format
2590       dopts_time_count = dopts_time_count + 1
2591       CALL check_open( 109 )
2592#if defined( __netcdf )
2593!
2594!--    Update the particle time series time axis
2595       nc_stat = NF90_PUT_VAR( id_set_pts, id_var_time_pts,      &
2596                               (/ time_since_reference_point /), &
2597                               start = (/ dopts_time_count /), count = (/ 1 /) )
2598       CALL netcdf_handle_error( 'data_output_ptseries', 391 )
2599#endif
2600
2601    ENDIF
2602
2603    ALLOCATE( pts_value(0:number_of_particle_groups,dopts_num), &
2604              pts_value_l(0:number_of_particle_groups,dopts_num) )
2605
2606    pts_value_l = 0.0_wp
2607    pts_value_l(:,16) = 9999999.9_wp    ! for calculation of minimum radius
2608
2609!
2610!-- Calculate or collect the particle time series quantities for all particles
2611!-- and seperately for each particle group (if there is more than one group)
2612    DO  i = nxl, nxr
2613       DO  j = nys, nyn
2614          DO  k = nzb, nzt
2615             number_of_particles = prt_count(k,j,i)
2616             IF (number_of_particles <= 0)  CYCLE
2617             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
2618             DO  n = 1, number_of_particles
2619
2620                IF ( particles(n)%particle_mask )  THEN  ! Restrict analysis to active particles
2621
2622                   pts_value_l(0,1)  = pts_value_l(0,1) + 1.0_wp  ! total # of particles
2623                   pts_value_l(0,2)  = pts_value_l(0,2) +                      &
2624                          ( particles(n)%x - particles(n)%origin_x )  ! mean x
2625                   pts_value_l(0,3)  = pts_value_l(0,3) +                      &
2626                          ( particles(n)%y - particles(n)%origin_y )  ! mean y
2627                   pts_value_l(0,4)  = pts_value_l(0,4) +                      &
2628                          ( particles(n)%z - particles(n)%origin_z )  ! mean z
2629                   pts_value_l(0,5)  = pts_value_l(0,5) + particles(n)%z        ! mean z (absolute)
2630                   pts_value_l(0,6)  = pts_value_l(0,6) + particles(n)%speed_x  ! mean u
2631                   pts_value_l(0,7)  = pts_value_l(0,7) + particles(n)%speed_y  ! mean v
2632                   pts_value_l(0,8)  = pts_value_l(0,8) + particles(n)%speed_z  ! mean w
2633                   pts_value_l(0,9)  = pts_value_l(0,9)  + particles(n)%rvar1 ! mean sgsu
2634                   pts_value_l(0,10) = pts_value_l(0,10) + particles(n)%rvar2 ! mean sgsv
2635                   pts_value_l(0,11) = pts_value_l(0,11) + particles(n)%rvar3 ! mean sgsw
2636                   IF ( particles(n)%speed_z > 0.0_wp )  THEN
2637                      pts_value_l(0,12) = pts_value_l(0,12) + 1.0_wp  ! # of upward moving prts
2638                      pts_value_l(0,13) = pts_value_l(0,13) +                  &
2639                                              particles(n)%speed_z ! mean w upw.
2640                   ELSE
2641                      pts_value_l(0,14) = pts_value_l(0,14) +                  &
2642                                              particles(n)%speed_z ! mean w down
2643                   ENDIF
2644                   pts_value_l(0,15) = pts_value_l(0,15) + particles(n)%radius ! mean rad
2645                   pts_value_l(0,16) = MIN( pts_value_l(0,16), particles(n)%radius ) ! minrad
2646                   pts_value_l(0,17) = MAX( pts_value_l(0,17), particles(n)%radius ) ! maxrad
2647                   pts_value_l(0,18) = pts_value_l(0,18) + 1.0_wp
2648                   pts_value_l(0,19) = pts_value_l(0,18) + 1.0_wp
2649!
2650!--                Repeat the same for the respective particle group
2651                   IF ( number_of_particle_groups > 1 )  THEN
2652                      jg = particles(n)%group
2653
2654                      pts_value_l(jg,1)  = pts_value_l(jg,1) + 1.0_wp
2655                      pts_value_l(jg,2)  = pts_value_l(jg,2) +                   &
2656                           ( particles(n)%x - particles(n)%origin_x )
2657                      pts_value_l(jg,3)  = pts_value_l(jg,3) +                   &
2658                           ( particles(n)%y - particles(n)%origin_y )
2659                      pts_value_l(jg,4)  = pts_value_l(jg,4) +                   &
2660                           ( particles(n)%z - particles(n)%origin_z )
2661                      pts_value_l(jg,5)  = pts_value_l(jg,5) + particles(n)%z
2662                      pts_value_l(jg,6)  = pts_value_l(jg,6) + particles(n)%speed_x
2663                      pts_value_l(jg,7)  = pts_value_l(jg,7) + particles(n)%speed_y
2664                      pts_value_l(jg,8)  = pts_value_l(jg,8) + particles(n)%speed_z
2665                      pts_value_l(jg,9)  = pts_value_l(jg,9)  + particles(n)%rvar1
2666                      pts_value_l(jg,10) = pts_value_l(jg,10) + particles(n)%rvar2
2667                      pts_value_l(jg,11) = pts_value_l(jg,11) + particles(n)%rvar3
2668                      IF ( particles(n)%speed_z > 0.0_wp )  THEN
2669                         pts_value_l(jg,12) = pts_value_l(jg,12) + 1.0_wp
2670                         pts_value_l(jg,13) = pts_value_l(jg,13) + particles(n)%speed_z
2671                      ELSE
2672                         pts_value_l(jg,14) = pts_value_l(jg,14) + particles(n)%speed_z
2673                      ENDIF
2674                      pts_value_l(jg,15) = pts_value_l(jg,15) + particles(n)%radius
2675                      pts_value_l(jg,16) = MIN( pts_value(jg,16), particles(n)%radius )
2676                      pts_value_l(jg,17) = MAX( pts_value(jg,17), particles(n)%radius )
2677                      pts_value_l(jg,18) = pts_value_l(jg,18) + 1.0_wp
2678                      pts_value_l(jg,19) = pts_value_l(jg,19) + 1.0_wp
2679                   ENDIF
2680
2681                ENDIF
2682
2683             ENDDO
2684
2685          ENDDO
2686       ENDDO
2687    ENDDO
2688
2689
2690#if defined( __parallel )
2691!
2692!-- Sum values of the subdomains
2693    inum = number_of_particle_groups + 1
2694
2695    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
2696    CALL MPI_ALLREDUCE( pts_value_l(0,1), pts_value(0,1), 15*inum, MPI_REAL, &
2697                        MPI_SUM, comm2d, ierr )
2698    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
2699    CALL MPI_ALLREDUCE( pts_value_l(0,16), pts_value(0,16), inum, MPI_REAL, &
2700                        MPI_MIN, comm2d, ierr )
2701    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
2702    CALL MPI_ALLREDUCE( pts_value_l(0,17), pts_value(0,17), inum, MPI_REAL, &
2703                        MPI_MAX, comm2d, ierr )
2704    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
2705    CALL MPI_ALLREDUCE( pts_value_l(0,18), pts_value(0,18), inum, MPI_REAL, &
2706                        MPI_MAX, comm2d, ierr )
2707    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
2708    CALL MPI_ALLREDUCE( pts_value_l(0,19), pts_value(0,19), inum, MPI_REAL, &
2709                        MPI_MIN, comm2d, ierr )
2710#else
2711    pts_value(:,1:19) = pts_value_l(:,1:19)
2712#endif
2713
2714!
2715!-- Normalize the above calculated quantities (except min/max values) with the
2716!-- total number of particles
2717    IF ( number_of_particle_groups > 1 )  THEN
2718       inum = number_of_particle_groups
2719    ELSE
2720       inum = 0
2721    ENDIF
2722
2723    DO  j = 0, inum
2724
2725       IF ( pts_value(j,1) > 0.0_wp )  THEN
2726
2727          pts_value(j,2:15) = pts_value(j,2:15) / pts_value(j,1)
2728          IF ( pts_value(j,12) > 0.0_wp  .AND.  pts_value(j,12) < 1.0_wp )  THEN
2729             pts_value(j,13) = pts_value(j,13) / pts_value(j,12)
2730             pts_value(j,14) = pts_value(j,14) / ( 1.0_wp - pts_value(j,12) )
2731          ELSEIF ( pts_value(j,12) == 0.0_wp )  THEN
2732             pts_value(j,13) = -1.0_wp
2733          ELSE
2734             pts_value(j,14) = -1.0_wp
2735          ENDIF
2736
2737       ENDIF
2738
2739    ENDDO
2740
2741!
2742!-- Calculate higher order moments of particle time series quantities,
2743!-- seperately for each particle group (if there is more than one group)
2744    DO  i = nxl, nxr
2745       DO  j = nys, nyn
2746          DO  k = nzb, nzt
2747             number_of_particles = prt_count(k,j,i)
2748             IF (number_of_particles <= 0)  CYCLE
2749             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
2750             DO  n = 1, number_of_particles
2751
2752                pts_value_l(0,20) = pts_value_l(0,20) + ( particles(n)%x - &
2753                                    particles(n)%origin_x - pts_value(0,2) )**2 ! x*2
2754                pts_value_l(0,21) = pts_value_l(0,21) + ( particles(n)%y - &
2755                                    particles(n)%origin_y - pts_value(0,3) )**2 ! y*2
2756                pts_value_l(0,22) = pts_value_l(0,22) + ( particles(n)%z - &
2757                                    particles(n)%origin_z - pts_value(0,4) )**2 ! z*2
2758                pts_value_l(0,23) = pts_value_l(0,23) + ( particles(n)%speed_x - &
2759                                                         pts_value(0,6) )**2   ! u*2
2760                pts_value_l(0,24) = pts_value_l(0,24) + ( particles(n)%speed_y - &
2761                                                          pts_value(0,7) )**2   ! v*2
2762                pts_value_l(0,25) = pts_value_l(0,25) + ( particles(n)%speed_z - &
2763                                                          pts_value(0,8) )**2   ! w*2
2764                pts_value_l(0,26) = pts_value_l(0,26) + ( particles(n)%rvar1 - &
2765                                                          pts_value(0,9) )**2   ! u"2
2766                pts_value_l(0,27) = pts_value_l(0,27) + ( particles(n)%rvar2 - &
2767                                                          pts_value(0,10) )**2  ! v"2
2768                pts_value_l(0,28) = pts_value_l(0,28) + ( particles(n)%rvar3 - &
2769                                                          pts_value(0,11) )**2  ! w"2
2770!
2771!--             Repeat the same for the respective particle group
2772                IF ( number_of_particle_groups > 1 )  THEN
2773                   jg = particles(n)%group
2774
2775                   pts_value_l(jg,20) = pts_value_l(jg,20) + ( particles(n)%x - &
2776                                       particles(n)%origin_x - pts_value(jg,2) )**2
2777                   pts_value_l(jg,21) = pts_value_l(jg,21) + ( particles(n)%y - &
2778                                       particles(n)%origin_y - pts_value(jg,3) )**2
2779                   pts_value_l(jg,22) = pts_value_l(jg,22) + ( particles(n)%z - &
2780                                       particles(n)%origin_z - pts_value(jg,4) )**2
2781                   pts_value_l(jg,23) = pts_value_l(jg,23) + ( particles(n)%speed_x - &
2782                                                             pts_value(jg,6) )**2
2783                   pts_value_l(jg,24) = pts_value_l(jg,24) + ( particles(n)%speed_y - &
2784                                                             pts_value(jg,7) )**2
2785                   pts_value_l(jg,25) = pts_value_l(jg,25) + ( particles(n)%speed_z - &
2786                                                             pts_value(jg,8) )**2
2787                   pts_value_l(jg,26) = pts_value_l(jg,26) + ( particles(n)%rvar1 - &
2788                                                             pts_value(jg,9) )**2
2789                   pts_value_l(jg,27) = pts_value_l(jg,27) + ( particles(n)%rvar2 - &
2790                                                             pts_value(jg,10) )**2
2791                   pts_value_l(jg,28) = pts_value_l(jg,28) + ( particles(n)%rvar3 - &
2792                                                             pts_value(jg,11) )**2
2793                ENDIF
2794
2795             ENDDO
2796          ENDDO
2797       ENDDO
2798    ENDDO
2799
2800    pts_value_l(0,29) = ( number_of_particles - pts_value(0,1) / numprocs )**2
2801                                                 ! variance of particle numbers
2802    IF ( number_of_particle_groups > 1 )  THEN
2803       DO  j = 1, number_of_particle_groups
2804          pts_value_l(j,29) = ( pts_value_l(j,1) - &
2805                                pts_value(j,1) / numprocs )**2
2806       ENDDO
2807    ENDIF
2808
2809#if defined( __parallel )
2810!
2811!-- Sum values of the subdomains
2812    inum = number_of_particle_groups + 1
2813
2814    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
2815    CALL MPI_ALLREDUCE( pts_value_l(0,20), pts_value(0,20), inum*10, MPI_REAL, &
2816                        MPI_SUM, comm2d, ierr )
2817#else
2818    pts_value(:,20:29) = pts_value_l(:,20:29)
2819#endif
2820
2821!
2822!-- Normalize the above calculated quantities with the total number of
2823!-- particles
2824    IF ( number_of_particle_groups > 1 )  THEN
2825       inum = number_of_particle_groups
2826    ELSE
2827       inum = 0
2828    ENDIF
2829
2830    DO  j = 0, inum
2831
2832       IF ( pts_value(j,1) > 0.0_wp )  THEN
2833          pts_value(j,20:28) = pts_value(j,20:28) / pts_value(j,1)
2834       ENDIF
2835       pts_value(j,29) = pts_value(j,29) / numprocs
2836
2837    ENDDO
2838
2839#if defined( __netcdf )
2840!
2841!-- Output particle time series quantities in NetCDF format
2842    IF ( myid == 0 )  THEN
2843       DO  j = 0, inum
2844          DO  i = 1, dopts_num
2845             nc_stat = NF90_PUT_VAR( id_set_pts, id_var_dopts(i,j),  &
2846                                     (/ pts_value(j,i) /),           &
2847                                     start = (/ dopts_time_count /), &
2848                                     count = (/ 1 /) )
2849             CALL netcdf_handle_error( 'data_output_ptseries', 392 )
2850          ENDDO
2851       ENDDO
2852    ENDIF
2853#endif
2854
2855    DEALLOCATE( pts_value, pts_value_l )
2856
2857    CALL cpu_log( log_point(36), 'data_output_ptseries', 'stop' )
2858
2859END SUBROUTINE lpm_data_output_ptseries
2860
2861 
2862!------------------------------------------------------------------------------!
2863! Description:
2864! ------------
2865!> This routine reads the respective restart data for the lpm.
2866!------------------------------------------------------------------------------!
2867 SUBROUTINE lpm_rrd_local_particles
2868
2869    CHARACTER (LEN=10) ::  particle_binary_version    !<
2870    CHARACTER (LEN=10) ::  version_on_file            !<
2871
2872    INTEGER(iwp) :: alloc_size !<
2873    INTEGER(iwp) :: ip         !<
2874    INTEGER(iwp) :: jp         !<
2875    INTEGER(iwp) :: kp         !<
2876
2877    TYPE(particle_type), DIMENSION(:), ALLOCATABLE :: tmp_particles !<
2878
2879!
2880!-- Read particle data from previous model run.
2881!-- First open the input unit.
2882    IF ( myid_char == '' )  THEN
2883       OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN'//myid_char,                  &
2884                  FORM='UNFORMATTED' )
2885    ELSE
2886       OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN/'//myid_char,                 &
2887                  FORM='UNFORMATTED' )
2888    ENDIF
2889
2890!
2891!-- First compare the version numbers
2892    READ ( 90 )  version_on_file
2893    particle_binary_version = '4.0'
2894    IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
2895       message_string = 'version mismatch concerning data from prior ' //      &
2896                        'run &version on file = "' //                          &
2897                                      TRIM( version_on_file ) //               &
2898                        '&version in program = "' //                           &
2899                                      TRIM( particle_binary_version ) // '"'
2900       CALL message( 'lpm_read_restart_file', 'PA0214', 1, 2, 0, 6, 0 )
2901    ENDIF
2902
2903!
2904!-- If less particles are stored on the restart file than prescribed by
2905!-- 1, the remainder is initialized by zero_particle to avoid
2906!-- errors.
2907    zero_particle = particle_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
2908                                   0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
2909                                   0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
2910                                   0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,     &
2911                                   0, 0, 0_idp, .FALSE., -1 )
2912!
2913!-- Read some particle parameters and the size of the particle arrays,
2914!-- allocate them and read their contents.
2915    READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                     &
2916                 last_particle_release_time, number_of_particle_groups,        &
2917                 particle_groups, time_write_particle_data
2918
2919    ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                        &
2920              grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2921
2922    READ ( 90 )  prt_count
2923
2924    DO  ip = nxl, nxr
2925       DO  jp = nys, nyn
2926          DO  kp = nzb+1, nzt
2927
2928             number_of_particles = prt_count(kp,jp,ip)
2929             IF ( number_of_particles > 0 )  THEN
2930                alloc_size = MAX( INT( number_of_particles *                   &
2931                             ( 1.0_wp + alloc_factor / 100.0_wp ) ),           &
2932                             1 )
2933             ELSE
2934                alloc_size = 1
2935             ENDIF
2936
2937             ALLOCATE( grid_particles(kp,jp,ip)%particles(1:alloc_size) )
2938
2939             IF ( number_of_particles > 0 )  THEN
2940                ALLOCATE( tmp_particles(1:number_of_particles) )
2941                READ ( 90 )  tmp_particles
2942                grid_particles(kp,jp,ip)%particles(1:number_of_particles) = tmp_particles
2943                DEALLOCATE( tmp_particles )
2944                IF ( number_of_particles < alloc_size )  THEN
2945                   grid_particles(kp,jp,ip)%particles(number_of_particles+1:alloc_size) &
2946                      = zero_particle
2947                ENDIF
2948             ELSE
2949                grid_particles(kp,jp,ip)%particles(1:alloc_size) = zero_particle
2950             ENDIF
2951
2952          ENDDO
2953       ENDDO
2954    ENDDO
2955
2956    CLOSE ( 90 )
2957!
2958!-- Must be called to sort particles into blocks, which is needed for a fast
2959!-- interpolation of the LES fields on the particle position.
2960    CALL lpm_sort_and_delete
2961
2962
2963 END SUBROUTINE lpm_rrd_local_particles
2964 
2965 
2966 SUBROUTINE lpm_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,          &
2967                              nxr_on_file, nynf, nync, nyn_on_file, nysf,  &
2968                              nysc, nys_on_file, tmp_3d, found )
2969
2970
2971   USE control_parameters,                                                 &
2972       ONLY: length, restart_string
2973
2974    INTEGER(iwp) ::  k               !<
2975    INTEGER(iwp) ::  nxlc            !<
2976    INTEGER(iwp) ::  nxlf            !<
2977    INTEGER(iwp) ::  nxl_on_file     !<
2978    INTEGER(iwp) ::  nxrc            !<
2979    INTEGER(iwp) ::  nxrf            !<
2980    INTEGER(iwp) ::  nxr_on_file     !<
2981    INTEGER(iwp) ::  nync            !<
2982    INTEGER(iwp) ::  nynf            !<
2983    INTEGER(iwp) ::  nyn_on_file     !<
2984    INTEGER(iwp) ::  nysc            !<
2985    INTEGER(iwp) ::  nysf            !<
2986    INTEGER(iwp) ::  nys_on_file     !<
2987
2988    LOGICAL, INTENT(OUT)  ::  found
2989
2990    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
2991
2992
2993    found = .TRUE.
2994
2995    SELECT CASE ( restart_string(1:length) )
2996
2997       CASE ( 'iran' ) ! matching random numbers is still unresolved issue
2998          IF ( k == 1 )  READ ( 13 )  iran, iran_part
2999
3000        CASE ( 'pc_av' )
3001           IF ( .NOT. ALLOCATED( pc_av ) )  THEN
3002              ALLOCATE( pc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
3003           ENDIF
3004           IF ( k == 1 )  READ ( 13 )  tmp_3d
3005           pc_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
3006              tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3007
3008        CASE ( 'pr_av' )
3009           IF ( .NOT. ALLOCATED( pr_av ) )  THEN
3010              ALLOCATE( pr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
3011           ENDIF
3012           IF ( k == 1 )  READ ( 13 )  tmp_3d
3013           pr_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
3014              tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3015 
3016         CASE ( 'ql_c_av' )
3017            IF ( .NOT. ALLOCATED( ql_c_av ) )  THEN
3018               ALLOCATE( ql_c_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
3019            ENDIF
3020            IF ( k == 1 )  READ ( 13 )  tmp_3d
3021            ql_c_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =        &
3022               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3023
3024         CASE ( 'ql_v_av' )
3025            IF ( .NOT. ALLOCATED( ql_v_av ) )  THEN
3026               ALLOCATE( ql_v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
3027            ENDIF
3028            IF ( k == 1 )  READ ( 13 )  tmp_3d
3029            ql_v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =        &
3030               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3031
3032         CASE ( 'ql_vp_av' )
3033            IF ( .NOT. ALLOCATED( ql_vp_av ) )  THEN
3034               ALLOCATE( ql_vp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
3035            ENDIF
3036            IF ( k == 1 )  READ ( 13 )  tmp_3d
3037            ql_vp_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =       &
3038               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
3039
3040          CASE DEFAULT
3041
3042             found = .FALSE.
3043
3044       END SELECT
3045               
3046
3047 END SUBROUTINE lpm_rrd_local
3048 
3049!------------------------------------------------------------------------------!
3050! Description:
3051! ------------
3052!> This routine writes the respective restart data for the lpm.
3053!------------------------------------------------------------------------------!
3054 SUBROUTINE lpm_wrd_local
3055 
3056    CHARACTER (LEN=10) ::  particle_binary_version   !<
3057
3058    INTEGER(iwp) ::  ip                              !<
3059    INTEGER(iwp) ::  jp                              !<
3060    INTEGER(iwp) ::  kp                              !<
3061!
3062!-- First open the output unit.
3063    IF ( myid_char == '' )  THEN
3064       OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT'//myid_char, &
3065                  FORM='UNFORMATTED')
3066    ELSE
3067       IF ( myid == 0 )  CALL local_system( 'mkdir PARTICLE_RESTART_DATA_OUT' )
3068#if defined( __parallel )
3069!
3070!--    Set a barrier in order to allow that thereafter all other processors
3071!--    in the directory created by PE0 can open their file
3072       CALL MPI_BARRIER( comm2d, ierr )
3073#endif
3074       OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT/'//myid_char, &
3075                  FORM='UNFORMATTED' )
3076    ENDIF
3077
3078!
3079!-- Write the version number of the binary format.
3080!-- Attention: After changes to the following output commands the version
3081!-- ---------  number of the variable particle_binary_version must be
3082!--            changed! Also, the version number and the list of arrays
3083!--            to be read in lpm_read_restart_file must be adjusted
3084!--            accordingly.
3085    particle_binary_version = '4.0'
3086    WRITE ( 90 )  particle_binary_version
3087
3088!
3089!-- Write some particle parameters, the size of the particle arrays
3090    WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                    &
3091                  last_particle_release_time, number_of_particle_groups,       &
3092                  particle_groups, time_write_particle_data
3093
3094    WRITE ( 90 )  prt_count
3095         
3096    DO  ip = nxl, nxr
3097       DO  jp = nys, nyn
3098          DO  kp = nzb+1, nzt
3099             number_of_particles = prt_count(kp,jp,ip)
3100             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
3101             IF ( number_of_particles <= 0 )  CYCLE
3102             WRITE ( 90 )  particles
3103          ENDDO
3104       ENDDO
3105    ENDDO
3106
3107    CLOSE ( 90 )
3108
3109#if defined( __parallel )
3110       CALL MPI_BARRIER( comm2d, ierr )
3111#endif
3112
3113    CALL wrd_write_string( 'iran' ) 
3114    WRITE ( 14 )  iran, iran_part 
3115
3116
3117 END SUBROUTINE lpm_wrd_local
3118
3119
3120!------------------------------------------------------------------------------!
3121! Description:
3122! ------------
3123!> This routine writes the respective restart data for the lpm.
3124!------------------------------------------------------------------------------!
3125 SUBROUTINE lpm_wrd_global
3126 
3127    CALL wrd_write_string( 'curvature_solution_effects' ) 
3128    WRITE ( 14 )  curvature_solution_effects
3129
3130 END SUBROUTINE lpm_wrd_global
3131 
3132
3133!------------------------------------------------------------------------------!
3134! Description:
3135! ------------
3136!> This routine writes the respective restart data for the lpm.
3137!------------------------------------------------------------------------------!
3138 SUBROUTINE lpm_rrd_global( found )
3139 
3140    USE control_parameters,                            &
3141        ONLY: length, restart_string
3142
3143    LOGICAL, INTENT(OUT)  ::  found
3144
3145    found = .TRUE.
3146
3147    SELECT CASE ( restart_string(1:length) )
3148
3149       CASE ( 'curvature_solution_effects' )
3150          READ ( 13 )  curvature_solution_effects
3151         
3152!          CASE ( 'global_paramter' )
3153!             READ ( 13 )  global_parameter
3154!          CASE ( 'global_array' )
3155!             IF ( .NOT. ALLOCATED( global_array ) )  ALLOCATE( global_array(1:10) )
3156!             READ ( 13 )  global_array
3157
3158       CASE DEFAULT
3159
3160          found = .FALSE.
3161
3162    END SELECT
3163   
3164 END SUBROUTINE lpm_rrd_global
3165
3166
3167!------------------------------------------------------------------------------!
3168! Description:
3169! ------------
3170!> This is a submodule of the lagrangian particle model. It contains all
3171!> dynamic processes of the lpm. This includes the advection (resolved and sub-
3172!> grid scale) as well as the boundary conditions of particles. As a next step
3173!> this submodule should be excluded as an own file.
3174!------------------------------------------------------------------------------!
3175 SUBROUTINE lpm_advec (interpolation_method,ip,jp,kp)
3176
3177    CHARACTER (LEN=*), INTENT(IN) ::  interpolation_method !<
3178    LOGICAL ::  subbox_at_wall !< flag to see if the current subgridbox is adjacent to a wall
3179
3180    INTEGER(iwp) ::  i                           !< index variable along x
3181    INTEGER(iwp) ::  i_next                      !< index variable along x
3182    INTEGER(iwp) ::  ip                          !< index variable along x
3183    INTEGER(iwp) ::  iteration_steps = 1         !< amount of iterations steps for corrector step
3184    INTEGER(iwp) ::  j                           !< index variable along y
3185    INTEGER(iwp) ::  j_next                      !< index variable along y
3186    INTEGER(iwp) ::  jp                          !< index variable along y
3187    INTEGER(iwp) ::  k                           !< index variable along z
3188    INTEGER(iwp) ::  k_wall                      !< vertical index of topography top
3189    INTEGER(iwp) ::  kp                          !< index variable along z
3190    INTEGER(iwp) ::  k_next                      !< index variable along z
3191    INTEGER(iwp) ::  kw                          !< index variable along z
3192    INTEGER(iwp) ::  kkw                         !< index variable along z
3193    INTEGER(iwp) ::  n                           !< loop variable over all particles in a grid box
3194    INTEGER(iwp) ::  nb                          !< block number particles are sorted in
3195    INTEGER(iwp) ::  particle_end                !< end index for partilce loop
3196    INTEGER(iwp) ::  particle_start              !< start index for particle loop
3197    INTEGER(iwp) ::  surf_start                  !< Index on surface data-type for current grid box
3198    INTEGER(iwp) ::  subbox_end                  !< end index for loop over subboxes in particle advection
3199    INTEGER(iwp) ::  subbox_start                !< start index for loop over subboxes in particle advection
3200    INTEGER(iwp) ::  nn                          !< loop variable over iterations steps
3201
3202    INTEGER(iwp), DIMENSION(0:7) ::  start_index !< start particle index for current block
3203    INTEGER(iwp), DIMENSION(0:7) ::  end_index   !< start particle index for current block
3204
3205    REAL(wp) ::  aa                 !< dummy argument for horizontal particle interpolation
3206    REAL(wp) ::  alpha              !< interpolation facor for x-direction
3207
3208    REAL(wp) ::  bb                 !< dummy argument for horizontal particle interpolation
3209    REAL(wp) ::  beta               !< interpolation facor for y-direction
3210    REAL(wp) ::  cc                 !< dummy argument for horizontal particle interpolation
3211    REAL(wp) ::  d_z_p_z0           !< inverse of interpolation length for logarithmic interpolation
3212    REAL(wp) ::  dd                 !< dummy argument for horizontal particle interpolation
3213    REAL(wp) ::  de_dx_int_l        !< x/y-interpolated TKE gradient (x) at particle position at lower vertical level
3214    REAL(wp) ::  de_dx_int_u        !< x/y-interpolated TKE gradient (x) at particle position at upper vertical level
3215    REAL(wp) ::  de_dy_int_l        !< x/y-interpolated TKE gradient (y) at particle position at lower vertical level
3216    REAL(wp) ::  de_dy_int_u        !< x/y-interpolated TKE gradient (y) at particle position at upper vertical level
3217    REAL(wp) ::  de_dt              !< temporal derivative of TKE experienced by the particle
3218    REAL(wp) ::  de_dt_min          !< lower level for temporal TKE derivative
3219    REAL(wp) ::  de_dz_int_l        !< x/y-interpolated TKE gradient (z) at particle position at lower vertical level
3220    REAL(wp) ::  de_dz_int_u        !< x/y-interpolated TKE gradient (z) at particle position at upper vertical level
3221    REAL(wp) ::  diameter           !< diamter of droplet
3222    REAL(wp) ::  diss_int_l         !< x/y-interpolated dissipation at particle position at lower vertical level
3223    REAL(wp) ::  diss_int_u         !< x/y-interpolated dissipation at particle position at upper vertical level
3224    REAL(wp) ::  dt_particle_m      !< previous particle time step
3225    REAL(wp) ::  dz_temp            !< dummy for the vertical grid spacing
3226    REAL(wp) ::  e_int_l            !< x/y-interpolated TKE at particle position at lower vertical level
3227    REAL(wp) ::  e_int_u            !< x/y-interpolated TKE at particle position at upper vertical level
3228    REAL(wp) ::  e_mean_int         !< horizontal mean TKE at particle height
3229    REAL(wp) ::  exp_arg            !< argument in the exponent - particle radius
3230    REAL(wp) ::  exp_term           !< exponent term
3231    REAL(wp) ::  gamma              !< interpolation facor for z-direction
3232    REAL(wp) ::  gg                 !< dummy argument for horizontal particle interpolation
3233    REAL(wp) ::  height_p           !< dummy argument for logarithmic interpolation
3234    REAL(wp) ::  log_z_z0_int       !< logarithmus used for surface_layer interpolation
3235    REAL(wp) ::  random_gauss       !< Gaussian-distributed random number used for SGS particle advection
3236    REAL(wp) ::  RL                 !< Lagrangian autocorrelation coefficient
3237    REAL(wp) ::  rg1                !< Gaussian distributed random number
3238    REAL(wp) ::  rg2                !< Gaussian distributed random number
3239    REAL(wp) ::  rg3                !< Gaussian distributed random number
3240    REAL(wp) ::  sigma              !< velocity standard deviation
3241    REAL(wp) ::  u_int_l            !< x/y-interpolated u-component at particle position at lower vertical level
3242    REAL(wp) ::  u_int_u            !< x/y-interpolated u-component at particle position at upper vertical level
3243    REAL(wp) ::  unext              !< calculated particle u-velocity of corrector step
3244    REAL(wp) ::  us_int             !< friction velocity at particle grid box
3245    REAL(wp) ::  usws_int           !< surface momentum flux (u component) at particle grid box
3246    REAL(wp) ::  v_int_l            !< x/y-interpolated v-component at particle position at lower vertical level
3247    REAL(wp) ::  v_int_u            !< x/y-interpolated v-component at particle position at upper vertical level
3248    REAL(wp) ::  vsws_int           !< surface momentum flux (u component) at particle grid box
3249    REAL(wp) ::  vnext              !< calculated particle v-velocity of corrector step
3250    REAL(wp) ::  vv_int             !< dummy to compute interpolated mean SGS TKE, used to scale SGS advection
3251    REAL(wp) ::  w_int_l            !< x/y-interpolated w-component at particle position at lower vertical level
3252    REAL(wp) ::  w_int_u            !< x/y-interpolated w-component at particle position at upper vertical level
3253    REAL(wp) ::  wnext              !< calculated particle w-velocity of corrector step
3254    REAL(wp) ::  w_s                !< terminal velocity of droplets
3255    REAL(wp) ::  x                  !< dummy argument for horizontal particle interpolation
3256    REAL(wp) ::  xp                 !< calculated particle position in x of predictor step
3257    REAL(wp) ::  y                  !< dummy argument for horizontal particle interpolation
3258    REAL(wp) ::  yp                 !< calculated particle position in y of predictor step
3259    REAL(wp) ::  z_p                !< surface layer height (0.5 dz)
3260    REAL(wp) ::  zp                 !< calculated particle position in z of predictor step
3261
3262    REAL(wp), PARAMETER ::  a_rog = 9.65_wp      !< parameter for fall velocity
3263    REAL(wp), PARAMETER ::  b_rog = 10.43_wp     !< parameter for fall velocity
3264    REAL(wp), PARAMETER ::  c_rog = 0.6_wp       !< parameter for fall velocity
3265    REAL(wp), PARAMETER ::  k_cap_rog = 4.0_wp   !< parameter for fall velocity
3266    REAL(wp), PARAMETER ::  k_low_rog = 12.0_wp  !< parameter for fall velocity
3267    REAL(wp), PARAMETER ::  d0_rog = 0.745_wp    !< separation diameter
3268
3269    REAL(wp), DIMENSION(number_of_particles) ::  term_1_2       !< flag to communicate whether a particle is near topography or not
3270    REAL(wp), DIMENSION(number_of_particles) ::  dens_ratio     !< ratio between the density of the fluid and the density of the particles
3271    REAL(wp), DIMENSION(number_of_particles) ::  de_dx_int      !< horizontal TKE gradient along x at particle position
3272    REAL(wp), DIMENSION(number_of_particles) ::  de_dy_int      !< horizontal TKE gradient along y at particle position
3273    REAL(wp), DIMENSION(number_of_particles) ::  de_dz_int      !< horizontal TKE gradient along z at particle position
3274    REAL(wp), DIMENSION(number_of_particles) ::  diss_int       !< dissipation at particle position
3275    REAL(wp), DIMENSION(number_of_particles) ::  dt_gap         !< remaining time until particle time integration reaches LES time
3276    REAL(wp), DIMENSION(number_of_particles) ::  dt_particle    !< particle time step
3277    REAL(wp), DIMENSION(number_of_particles) ::  e_int          !< TKE at particle position
3278    REAL(wp), DIMENSION(number_of_particles) ::  fs_int         !< weighting factor for subgrid-scale particle speed
3279    REAL(wp), DIMENSION(number_of_particles) ::  lagr_timescale !< Lagrangian timescale
3280    REAL(wp), DIMENSION(number_of_particles) ::  rvar1_temp     !< SGS particle velocity - u-component
3281    REAL(wp), DIMENSION(number_of_particles) ::  rvar2_temp     !< SGS particle velocity - v-component
3282    REAL(wp), DIMENSION(number_of_particles) ::  rvar3_temp     !< SGS particle velocity - w-component
3283    REAL(wp), DIMENSION(number_of_particles) ::  u_int          !< u-component of particle speed
3284    REAL(wp), DIMENSION(number_of_particles) ::  v_int          !< v-component of particle speed
3285    REAL(wp), DIMENSION(number_of_particles) ::  w_int          !< w-component of particle speed
3286    REAL(wp), DIMENSION(number_of_particles) ::  xv             !< x-position
3287    REAL(wp), DIMENSION(number_of_particles) ::  yv             !< y-position
3288    REAL(wp), DIMENSION(number_of_particles) ::  zv             !< z-position
3289
3290    REAL(wp), DIMENSION(number_of_particles, 3) ::  rg !< vector of Gaussian distributed random numbers
3291
3292    CALL cpu_log( log_point_s(44), 'lpm_advec', 'continue' )
3293!
3294!-- Determine height of Prandtl layer and distance between Prandtl-layer
3295!-- height and horizontal mean roughness height, which are required for
3296!-- vertical logarithmic interpolation of horizontal particle speeds
3297!-- (for particles below first vertical grid level).
3298    z_p      = zu(nzb+1) - zw(nzb)
3299    d_z_p_z0 = 1.0_wp / ( z_p - z0_av_global )
3300
3301    xv = particles(1:number_of_particles)%x
3302    yv = particles(1:number_of_particles)%y
3303    zv = particles(1:number_of_particles)%z
3304    dt_particle = dt_3d
3305
3306
3307    SELECT CASE ( interpolation_method )
3308
3309!
3310!--    This case uses a simple interpolation method for the particle velocites,
3311!--    and applying a predictor-corrector method. @attention: for the corrector
3312!--    step the velocities of t(n+1) are required. However, at this moment of
3313!--    the time integration they are not free of divergence. This interpolation
3314!--    method is described in more detail in Grabowski et al., 2018 (GMD).
3315       CASE ( 'simple_corrector' )
3316!
3317!--       Predictor step
3318          kkw = kp - 1
3319          DO n = 1, number_of_particles
3320
3321             alpha = MAX( MIN( ( particles(n)%x - ip * dx ) * ddx, 1.0_wp ), 0.0_wp )
3322             u_int(n) = u(kp,jp,ip) * ( 1.0_wp - alpha ) + u(kp,jp,ip+1) * alpha
3323
3324             beta  = MAX( MIN( ( particles(n)%y - jp * dy ) * ddy, 1.0_wp ), 0.0_wp )
3325             v_int(n) = v(kp,jp,ip) * ( 1.0_wp - beta ) + v(kp,jp+1,ip) * beta
3326
3327             gamma = MAX( MIN( ( particles(n)%z - zw(kkw) ) /                   &
3328                               ( zw(kkw+1) - zw(kkw) ), 1.0_wp ), 0.0_wp )
3329             w_int(n) = w(kkw,jp,ip) * ( 1.0_wp - gamma ) + w(kkw+1,jp,ip) * gamma
3330
3331          ENDDO
3332
3333!
3334!--       Corrector step
3335          DO n = 1, number_of_particles
3336
3337             IF ( .NOT. particles(n)%particle_mask ) CYCLE
3338
3339             DO nn = 1, iteration_steps
3340
3341!
3342!--             Guess new position
3343                xp = particles(n)%x + u_int(n) * dt_particle(n)
3344                yp = particles(n)%y + v_int(n) * dt_particle(n)
3345                zp = particles(n)%z + w_int(n) * dt_particle(n)
3346!
3347!--             x direction
3348                i_next = FLOOR( xp * ddx , KIND=iwp)
3349                alpha  = MAX( MIN( ( xp - i_next * dx ) * ddx, 1.0_wp ), 0.0_wp )
3350!
3351!--             y direction
3352                j_next = FLOOR( yp * ddy )
3353                beta   = MAX( MIN( ( yp - j_next * dy ) * ddy, 1.0_wp ), 0.0_wp )
3354!
3355!--             z_direction
3356                k_next = MAX( MIN( FLOOR( zp / (zw(kkw+1)-zw(kkw)) ), nzt ), 0)
3357                gamma = MAX( MIN( ( zp - zw(k_next) ) /                      &
3358                                  ( zw(k_next+1) - zw(k_next) ), 1.0_wp ), 0.0_wp )
3359!
3360!--             Calculate part of the corrector step
3361                unext = u_p(k_next+1, j_next, i_next) * ( 1.0_wp - alpha ) +    &
3362                        u_p(k_next+1, j_next,   i_next+1) * alpha
3363
3364                vnext = v_p(k_next+1, j_next, i_next) * ( 1.0_wp - beta  ) +    &
3365                        v_p(k_next+1, j_next+1, i_next  ) * beta
3366
3367                wnext = w_p(k_next,   j_next, i_next) * ( 1.0_wp - gamma ) +    &
3368                        w_p(k_next+1, j_next, i_next  ) * gamma
3369
3370!
3371!--             Calculate interpolated particle velocity with predictor
3372!--             corrector step. u_int, v_int and w_int describes the part of
3373!--             the predictor step. unext, vnext and wnext is the part of the
3374!--             corrector step. The resulting new position is set below. The
3375!--             implementation is based on Grabowski et al., 2018 (GMD).
3376                u_int(n) = 0.5_wp * ( u_int(n) + unext )
3377                v_int(n) = 0.5_wp * ( v_int(n) + vnext )
3378                w_int(n) = 0.5_wp * ( w_int(n) + wnext )
3379
3380             ENDDO
3381          ENDDO
3382
3383
3384!
3385!--    This case uses a simple interpolation method for the particle velocites,
3386!--    and applying a predictor.
3387       CASE ( 'simple_predictor' )
3388!
3389!--       The particle position for the w velociy is based on the value of kp and kp-1
3390          kkw = kp - 1
3391          DO n = 1, number_of_particles
3392             IF ( .NOT. particles(n)%particle_mask ) CYCLE
3393
3394             alpha    = MAX( MIN( ( particles(n)%x - ip * dx ) * ddx, 1.0_wp ), 0.0_wp )
3395             u_int(n) = u(kp,jp,ip) * ( 1.0_wp - alpha ) + u(kp,jp,ip+1) * alpha
3396
3397             beta     = MAX( MIN( ( particles(n)%y - jp * dy ) * ddy, 1.0_wp ), 0.0_wp )
3398             v_int(n) = v(kp,jp,ip) * ( 1.0_wp - beta ) + v(kp,jp+1,ip) * beta
3399
3400             gamma    = MAX( MIN( ( particles(n)%z - zw(kkw) ) /                   &
3401                                  ( zw(kkw+1) - zw(kkw) ), 1.0_wp ), 0.0_wp )
3402             w_int(n) = w(kkw,jp,ip) * ( 1.0_wp - gamma ) + w(kkw+1,jp,ip) * gamma
3403          ENDDO
3404!
3405!--    The trilinear interpolation.
3406       CASE ( 'trilinear' )
3407
3408          start_index = grid_particles(kp,jp,ip)%start_index
3409          end_index   = grid_particles(kp,jp,ip)%end_index
3410
3411          DO  nb = 0, 7
3412!
3413!--          Interpolate u velocity-component
3414             i = ip
3415             j = jp + block_offset(nb)%j_off
3416             k = kp + block_offset(nb)%k_off
3417
3418             DO  n = start_index(nb), end_index(nb)
3419!
3420!--             Interpolation of the u velocity component onto particle position.
3421!--             Particles are interpolation bi-linearly in the horizontal and a
3422!--             linearly in the vertical. An exception is made for particles below
3423!--             the first vertical grid level in case of a prandtl layer. In this
3424!--             case the horizontal particle velocity components are determined using
3425!--             Monin-Obukhov relations (if branch).
3426!--             First, check if particle is located below first vertical grid level
3427!--             above topography (Prandtl-layer height)
3428!--             Determine vertical index of topography top
3429                k_wall = get_topography_top_index_ji( jp, ip, 's' )
3430
3431                IF ( constant_flux_layer  .AND.  zv(n) - zw(k_wall) < z_p )  THEN
3432!
3433!--                Resolved-scale horizontal particle velocity is zero below z0.
3434                   IF ( zv(n) - zw(k_wall) < z0_av_global )  THEN
3435                      u_int(n) = 0.0_wp
3436                   ELSE
3437!
3438!--                   Determine the sublayer. Further used as index.
3439                      height_p = ( zv(n) - zw(k_wall) - z0_av_global ) &
3440                                           * REAL( number_of_sublayers, KIND=wp )    &
3441                                           * d_z_p_z0
3442!
3443!--                   Calculate LOG(z/z0) for exact particle height. Therefore,
3444!--                   interpolate linearly between precalculated logarithm.
3445                      log_z_z0_int = log_z_z0(INT(height_p))                         &
3446                                       + ( height_p - INT(height_p) )                &
3447                                       * ( log_z_z0(INT(height_p)+1)                 &
3448                                            - log_z_z0(INT(height_p))                &
3449                                         )
3450!
3451!--                   Get friction velocity and momentum flux from new surface data
3452!--                   types.
3453                      IF ( surf_def_h(0)%start_index(jp,ip) <=                   &
3454                           surf_def_h(0)%end_index(jp,ip) )  THEN
3455                         surf_start = surf_def_h(0)%start_index(jp,ip)
3456!--                      Limit friction velocity. In narrow canyons or holes the
3457!--                      friction velocity can become very small, resulting in a too
3458!--                      large particle speed.
3459                         us_int    = MAX( surf_def_h(0)%us(surf_start), 0.01_wp )
3460                         usws_int  = surf_def_h(0)%usws(surf_start)
3461                      ELSEIF ( surf_lsm_h%start_index(jp,ip) <=                  &
3462                               surf_lsm_h%end_index(jp,ip) )  THEN
3463                         surf_start = surf_lsm_h%start_index(jp,ip)
3464                         us_int    = MAX( surf_lsm_h%us(surf_start), 0.01_wp )
3465                         usws_int  = surf_lsm_h%usws(surf_start)
3466                      ELSEIF ( surf_usm_h%start_index(jp,ip) <=                  &
3467                               surf_usm_h%end_index(jp,ip) )  THEN
3468                         surf_start = surf_usm_h%start_index(jp,ip)
3469                         us_int    = MAX( surf_usm_h%us(surf_start), 0.01_wp )
3470                         usws_int  = surf_usm_h%usws(surf_start)
3471                      ENDIF
3472!
3473!--                   Neutral solution is applied for all situations, e.g. also for
3474!--                   unstable and stable situations. Even though this is not exact
3475!--                   this saves a lot of CPU time since several calls of intrinsic
3476!--                   FORTRAN procedures (LOG, ATAN) are avoided, This is justified
3477!--                   as sensitivity studies revealed no significant effect of
3478!--                   using the neutral solution also for un/stable situations.
3479                      u_int(n) = -usws_int / ( us_int * kappa + 1E-10_wp )           &
3480                                  * log_z_z0_int - u_gtrans
3481                   ENDIF
3482!
3483!--             Particle above the first grid level. Bi-linear interpolation in the
3484!--             horizontal and linear interpolation in the vertical direction.
3485                ELSE
3486                   x  = xv(n) - i * dx
3487                   y  = yv(n) + ( 0.5_wp - j ) * dy
3488                   aa = x**2          + y**2
3489                   bb = ( dx - x )**2 + y**2
3490                   cc = x**2          + ( dy - y )**2
3491                   dd = ( dx - x )**2 + ( dy - y )**2
3492                   gg = aa + bb + cc + dd
3493
3494                   u_int_l = ( ( gg - aa ) * u(k,j,i)   + ( gg - bb ) * u(k,j,i+1)   &
3495                               + ( gg - cc ) * u(k,j+1,i) + ( gg - dd ) *            &
3496                               u(k,j+1,i+1) ) / ( 3.0_wp * gg ) - u_gtrans
3497
3498                   IF ( k == nzt )  THEN
3499                      u_int(n) = u_int_l
3500                   ELSE
3501                      u_int_u = ( ( gg-aa ) * u(k+1,j,i) + ( gg-bb ) * u(k+1,j,i+1)  &
3502                                  + ( gg-cc ) * u(k+1,j+1,i) + ( gg-dd ) *           &
3503                                  u(k+1,j+1,i+1) ) / ( 3.0_wp * gg ) - u_gtrans
3504                      u_int(n) = u_int_l + ( zv(n) - zu(k) ) / dzw(k+1) *            &
3505                                 ( u_int_u - u_int_l )
3506                   ENDIF
3507                ENDIF
3508             ENDDO
3509!
3510!--          Same procedure for interpolation of the v velocity-component
3511             i = ip + block_offset(nb)%i_off
3512             j = jp
3513             k = kp + block_offset(nb)%k_off
3514
3515             DO  n = start_index(nb), end_index(nb)
3516!
3517!--             Determine vertical index of topography top
3518                k_wall = get_topography_top_index_ji( jp,ip, 's' )
3519
3520                IF ( constant_flux_layer  .AND.  zv(n) - zw(k_wall) < z_p )  THEN
3521                   IF ( zv(n) - zw(k_wall) < z0_av_global )  THEN
3522!
3523!--                   Resolved-scale horizontal particle velocity is zero below z0.
3524                      v_int(n) = 0.0_wp
3525                   ELSE
3526!
3527!--                   Determine the sublayer. Further used as index. Please note,
3528!--                   logarithmus can not be reused from above, as in in case of
3529!--                   topography particle on u-grid can be above surface-layer height,
3530!--                   whereas it can be below on v-grid.
3531                      height_p = ( zv(n) - zw(k_wall) - z0_av_global ) &
3532                                        * REAL( number_of_sublayers, KIND=wp )       &
3533                                        * d_z_p_z0
3534!
3535!--                   Calculate LOG(z/z0) for exact particle height. Therefore,
3536!--                   interpolate linearly between precalculated logarithm.
3537                      log_z_z0_int = log_z_z0(INT(height_p))                         &
3538                                       + ( height_p - INT(height_p) )                &
3539                                       * ( log_z_z0(INT(height_p)+1)                 &
3540                                            - log_z_z0(INT(height_p))                &
3541                                         )
3542!
3543!--                   Get friction velocity and momentum flux from new surface data
3544!--                   types.
3545                      IF ( surf_def_h(0)%start_index(jp,ip) <=                   &
3546                           surf_def_h(0)%end_index(jp,ip) )  THEN
3547                         surf_start = surf_def_h(0)%start_index(jp,ip)
3548!--                      Limit friction velocity. In narrow canyons or holes the
3549!--                      friction velocity can become very small, resulting in a too
3550!--                      large particle speed.
3551                         us_int    = MAX( surf_def_h(0)%us(surf_start), 0.01_wp )
3552                         vsws_int  = surf_def_h(0)%vsws(surf_start)
3553                      ELSEIF ( surf_lsm_h%start_index(jp,ip) <=                  &
3554                               surf_lsm_h%end_index(jp,ip) )  THEN
3555                         surf_start = surf_lsm_h%start_index(jp,ip)
3556                         us_int    = MAX( surf_lsm_h%us(surf_start), 0.01_wp )
3557                         vsws_int  = surf_lsm_h%vsws(surf_start)
3558                      ELSEIF ( surf_usm_h%start_index(jp,ip) <=                  &
3559                               surf_usm_h%end_index(jp,ip) )  THEN
3560                         surf_start = surf_usm_h%start_index(jp,ip)
3561                         us_int    = MAX( surf_usm_h%us(surf_start), 0.01_wp )
3562                         vsws_int  = surf_usm_h%vsws(surf_start)
3563                      ENDIF
3564!
3565!--                   Neutral solution is applied for all situations, e.g. also for
3566!--                   unstable and stable situations. Even though this is not exact
3567!--                   this saves a lot of CPU time since several calls of intrinsic
3568!--                   FORTRAN procedures (LOG, ATAN) are avoided, This is justified
3569!--                   as sensitivity studies revealed no significant effect of
3570!--                   using the neutral solution also for un/stable situations.
3571                      v_int(n) = -vsws_int / ( us_int * kappa + 1E-10_wp )           &
3572                               * log_z_z0_int - v_gtrans
3573
3574                   ENDIF
3575                ELSE
3576                   x  = xv(n) + ( 0.5_wp - i ) * dx
3577                   y  = yv(n) - j * dy
3578                   aa = x**2          + y**2
3579                   bb = ( dx - x )**2 + y**2
3580                   cc = x**2          + ( dy - y )**2
3581                   dd = ( dx - x )**2 + ( dy - y )**2
3582                   gg = aa + bb + cc + dd
3583
3584                   v_int_l = ( ( gg - aa ) * v(k,j,i)   + ( gg - bb ) * v(k,j,i+1)   &
3585                             + ( gg - cc ) * v(k,j+1,i) + ( gg - dd ) * v(k,j+1,i+1) &
3586                             ) / ( 3.0_wp * gg ) - v_gtrans
3587
3588                   IF ( k == nzt )  THEN
3589                      v_int(n) = v_int_l
3590                   ELSE
3591                      v_int_u = ( ( gg-aa ) * v(k+1,j,i)   + ( gg-bb ) * v(k+1,j,i+1)   &
3592                                + ( gg-cc ) * v(k+1,j+1,i) + ( gg-dd ) * v(k+1,j+1,i+1) &
3593                                ) / ( 3.0_wp * gg ) - v_gtrans
3594                      v_int(n) = v_int_l + ( zv(n) - zu(k) ) / dzw(k+1) *               &
3595                                        ( v_int_u - v_int_l )
3596                   ENDIF
3597                ENDIF
3598             ENDDO
3599!
3600!--          Same procedure for interpolation of the w velocity-component
3601             i = ip + block_offset(nb)%i_off
3602             j = jp + block_offset(nb)%j_off
3603             k = kp - 1
3604
3605             DO  n = start_index(nb), end_index(nb)
3606                IF ( vertical_particle_advection(particles(n)%group) )  THEN
3607                   x  = xv(n) + ( 0.5_wp - i ) * dx
3608                   y  = yv(n) + ( 0.5_wp - j ) * dy
3609                   aa = x**2          + y**2
3610                   bb = ( dx - x )**2 + y**2
3611                   cc = x**2          + ( dy - y )**2
3612                   dd = ( dx - x )**2 + ( dy - y )**2
3613                   gg = aa + bb + cc + dd
3614
3615                   w_int_l = ( ( gg - aa ) * w(k,j,i)   + ( gg - bb ) * w(k,j,i+1)   &
3616                             + ( gg - cc ) * w(k,j+1,i) + ( gg - dd ) * w(k,j+1,i+1) &
3617                             ) / ( 3.0_wp * gg )
3618
3619                   IF ( k == nzt )  THEN
3620                      w_int(n) = w_int_l
3621                   ELSE
3622                      w_int_u = ( ( gg-aa ) * w(k+1,j,i)   + &
3623                                  ( gg-bb ) * w(k+1,j,i+1) + &
3624                                  ( gg-cc ) * w(k+1,j+1,i) + &
3625                                  ( gg-dd ) * w(k+1,j+1,i+1) &
3626                                ) / ( 3.0_wp * gg )
3627                      w_int(n) = w_int_l + ( zv(n) - zw(k) ) / dzw(k+1) *               &
3628                                 ( w_int_u - w_int_l )
3629                   ENDIF
3630                ELSE
3631                   w_int(n) = 0.0_wp
3632                ENDIF
3633             ENDDO
3634          ENDDO
3635
3636       CASE DEFAULT
3637          WRITE( message_string, * )  'unknown particle velocity interpolation method = "',  &
3638                                       TRIM( interpolation_method ), '"'
3639          CALL message( 'lpm_advec', 'PA0660', 1, 2, 0, 6, 0 )
3640
3641    END SELECT
3642
3643!-- Interpolate and calculate quantities needed for calculating the SGS
3644!-- velocities
3645    IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets )  THEN
3646
3647       DO  nb = 0,7
3648
3649          subbox_at_wall = .FALSE.
3650!
3651!--       In case of topography check if subbox is adjacent to a wall
3652          IF ( .NOT. topography == 'flat' ) THEN
3653             i = ip + MERGE( -1_iwp , 1_iwp, BTEST( nb, 2 ) )
3654             j = jp + MERGE( -1_iwp , 1_iwp, BTEST( nb, 1 ) )
3655             k = kp + MERGE( -1_iwp , 1_iwp, BTEST( nb, 0 ) )
3656             IF ( .NOT. BTEST(wall_flags_0(k,  jp, ip), 0) .OR.                &
3657                  .NOT. BTEST(wall_flags_0(kp, j,  ip), 0) .OR.                &
3658                  .NOT. BTEST(wall_flags_0(kp, jp, i ), 0) )                   &
3659             THEN
3660                subbox_at_wall = .TRUE.
3661             ENDIF
3662          ENDIF
3663          IF ( subbox_at_wall ) THEN
3664             e_int(start_index(nb):end_index(nb))     = e(kp,jp,ip) 
3665             diss_int(start_index(nb):end_index(nb))  = diss(kp,jp,ip)
3666             de_dx_int(start_index(nb):end_index(nb)) = de_dx(kp,jp,ip)
3667             de_dy_int(start_index(nb):end_index(nb)) = de_dy(kp,jp,ip)
3668             de_dz_int(start_index(nb):end_index(nb)) = de_dz(kp,jp,ip)
3669!
3670!--          Set flag for stochastic equation.
3671             term_1_2(start_index(nb):end_index(nb)) = 0.0_wp
3672          ELSE
3673             i = ip + block_offset(nb)%i_off
3674             j = jp + block_offset(nb)%j_off
3675             k = kp + block_offset(nb)%k_off
3676
3677             DO  n = start_index(nb), end_index(nb)
3678!
3679!--             Interpolate TKE
3680                x  = xv(n) + ( 0.5_wp - i ) * dx
3681                y  = yv(n) + ( 0.5_wp - j ) * dy
3682                aa = x**2          + y**2
3683                bb = ( dx - x )**2 + y**2
3684                cc = x**2          + ( dy - y )**2
3685                dd = ( dx - x )**2 + ( dy - y )**2
3686                gg = aa + bb + cc + dd
3687
3688                e_int_l = ( ( gg-aa ) * e(k,j,i)   + ( gg-bb ) * e(k,j,i+1)   &
3689                          + ( gg-cc ) * e(k,j+1,i) + ( gg-dd ) * e(k,j+1,i+1) &
3690                          ) / ( 3.0_wp * gg )
3691
3692                IF ( k+1 == nzt+1 )  THEN
3693                   e_int(n) = e_int_l
3694                ELSE
3695                   e_int_u = ( ( gg - aa ) * e(k+1,j,i)   + &
3696                               ( gg - bb ) * e(k+1,j,i+1) + &
3697                               ( gg - cc ) * e(k+1,j+1,i) + &
3698                               ( gg - dd ) * e(k+1,j+1,i+1) &
3699                            ) / ( 3.0_wp * gg )
3700                   e_int(n) = e_int_l + ( zv(n) - zu(k) ) / dzw(k+1) *            &
3701                                     ( e_int_u - e_int_l )
3702                ENDIF
3703!
3704!--             Needed to avoid NaN particle velocities (this might not be
3705!--             required any more)
3706                IF ( e_int(n) <= 0.0_wp )  THEN
3707                   e_int(n) = 1.0E-20_wp
3708                ENDIF
3709!
3710!--             Interpolate the TKE gradient along x (adopt incides i,j,k and
3711!--             all position variables from above (TKE))
3712                de_dx_int_l = ( ( gg - aa ) * de_dx(k,j,i)   + &
3713                                ( gg - bb ) * de_dx(k,j,i+1) + &
3714                                ( gg - cc ) * de_dx(k,j+1,i) + &
3715                                ( gg - dd ) * de_dx(k,j+1,i+1) &
3716                               ) / ( 3.0_wp * gg )
3717
3718                IF ( ( k+1 == nzt+1 )  .OR.  ( k == nzb ) )  THEN
3719                   de_dx_int(n) = de_dx_int_l
3720                ELSE
3721                   de_dx_int_u = ( ( gg - aa ) * de_dx(k+1,j,i)   + &
3722                                   ( gg - bb ) * de_dx(k+1,j,i+1) + &
3723                                   ( gg - cc ) * de_dx(k+1,j+1,i) + &
3724                                   ( gg - dd ) * de_dx(k+1,j+1,i+1) &
3725                                  ) / ( 3.0_wp * gg )
3726                   de_dx_int(n) = de_dx_int_l + ( zv(n) - zu(k) ) / dzw(k+1) *    &
3727                                              ( de_dx_int_u - de_dx_int_l )
3728                ENDIF
3729!
3730!--             Interpolate the TKE gradient along y
3731                de_dy_int_l = ( ( gg - aa ) * de_dy(k,j,i)   + &
3732                                ( gg - bb ) * de_dy(k,j,i+1) + &
3733                                ( gg - cc ) * de_dy(k,j+1,i) + &
3734                                ( gg - dd ) * de_dy(k,j+1,i+1) &
3735                               ) / ( 3.0_wp * gg )
3736                IF ( ( k+1 == nzt+1 )  .OR.  ( k == nzb ) )  THEN
3737                   de_dy_int(n) = de_dy_int_l
3738                ELSE
3739                   de_dy_int_u = ( ( gg - aa ) * de_dy(k+1,j,i)   + &
3740                                   ( gg - bb ) * de_dy(k+1,j,i+1) + &
3741                                   ( gg - cc ) * de_dy(k+1,j+1,i) + &
3742                                   ( gg - dd ) * de_dy(k+1,j+1,i+1) &
3743                                  ) / ( 3.0_wp * gg )
3744                      de_dy_int(n) = de_dy_int_l + ( zv(n) - zu(k) ) / dzw(k+1) * &
3745                                                 ( de_dy_int_u - de_dy_int_l )
3746                ENDIF
3747
3748!
3749!--             Interpolate the TKE gradient along z
3750                IF ( zv(n) < 0.5_wp * dz(1) )  THEN
3751                   de_dz_int(n) = 0.0_wp
3752                ELSE
3753                   de_dz_int_l = ( ( gg - aa ) * de_dz(k,j,i)   + &
3754                                   ( gg - bb ) * de_dz(k,j,i+1) + &
3755                                   ( gg - cc ) * de_dz(k,j+1,i) + &
3756                                   ( gg - dd ) * de_dz(k,j+1,i+1) &
3757                                  ) / ( 3.0_wp * gg )
3758
3759                   IF ( ( k+1 == nzt+1 )  .OR.  ( k == nzb ) )  THEN
3760                      de_dz_int(n) = de_dz_int_l
3761                   ELSE
3762                      de_dz_int_u = ( ( gg - aa ) * de_dz(k+1,j,i)   + &
3763                                      ( gg - bb ) * de_dz(k+1,j,i+1) + &
3764                                      ( gg - cc ) * de_dz(k+1,j+1,i) + &
3765                                      ( gg - dd ) * de_dz(k+1,j+1,i+1) &
3766                                     ) / ( 3.0_wp * gg )
3767                      de_dz_int(n) = de_dz_int_l + ( zv(n) - zu(k) ) / dzw(k+1) * &
3768                                                 ( de_dz_int_u - de_dz_int_l )
3769                   ENDIF
3770                ENDIF
3771
3772!
3773!--             Interpolate the dissipation of TKE
3774                diss_int_l = ( ( gg - aa ) * diss(k,j,i)   + &
3775                               ( gg - bb ) * diss(k,j,i+1) + &
3776                               ( gg - cc ) * diss(k,j+1,i) + &
3777                               ( gg - dd ) * diss(k,j+1,i+1) &
3778                               ) / ( 3.0_wp * gg )
3779
3780                IF ( k == nzt )  THEN
3781                   diss_int(n) = diss_int_l
3782                ELSE
3783                   diss_int_u = ( ( gg - aa ) * diss(k+1,j,i)   + &
3784                                  ( gg - bb ) * diss(k+1,j,i+1) + &
3785                                  ( gg - cc ) * diss(k+1,j+1,i) + &
3786                                  ( gg - dd ) * diss(k+1,j+1,i+1) &
3787                                 ) / ( 3.0_wp * gg )
3788                   diss_int(n) = diss_int_l + ( zv(n) - zu(k) ) / dzw(k+1) *      &
3789                                            ( diss_int_u - diss_int_l )
3790                ENDIF
3791
3792!
3793!--             Set flag for stochastic equation.
3794                term_1_2(n) = 1.0_wp
3795             ENDDO
3796          ENDIF
3797       ENDDO
3798
3799       DO nb = 0,7
3800          i = ip + block_offset(nb)%i_off
3801          j = jp + block_offset(nb)%j_off
3802          k = kp + block_offset(nb)%k_off
3803
3804          DO  n = start_index(nb), end_index(nb)
3805!
3806!--          Vertical interpolation of the horizontally averaged SGS TKE and
3807!--          resolved-scale velocity variances and use the interpolated values
3808!--          to calculate the coefficient fs, which is a measure of the ratio
3809!--          of the subgrid-scale turbulent kinetic energy to the total amount
3810!--          of turbulent kinetic energy.
3811             IF ( k == 0 )  THEN
3812                e_mean_int = hom(0,1,8,0)
3813             ELSE
3814                e_mean_int = hom(k,1,8,0) +                                    &
3815                                           ( hom(k+1,1,8,0) - hom(k,1,8,0) ) / &
3816                                           ( zu(k+1) - zu(k) ) *               &
3817                                           ( zv(n) - zu(k) )
3818             ENDIF
3819
3820             kw = kp - 1
3821
3822             IF ( k == 0 )  THEN
3823                aa  = hom(k+1,1,30,0)  * ( zv(n) / &
3824                                         ( 0.5_wp * ( zu(k+1) - zu(k) ) ) )
3825                bb  = hom(k+1,1,31,0)  * ( zv(n) / &
3826                                         ( 0.5_wp * ( zu(k+1) - zu(k) ) ) )
3827                cc  = hom(kw+1,1,32,0) * ( zv(n) / &
3828                                         ( 1.0_wp * ( zw(kw+1) - zw(kw) ) ) )
3829             ELSE
3830                aa  = hom(k,1,30,0) + ( hom(k+1,1,30,0) - hom(k,1,30,0) ) *    &
3831                           ( ( zv(n) - zu(k) ) / ( zu(k+1) - zu(k) ) )
3832                bb  = hom(k,1,31,0) + ( hom(k+1,1,31,0) - hom(k,1,31,0) ) *    &
3833                           ( ( zv(n) - zu(k) ) / ( zu(k+1) - zu(k) ) )
3834                cc  = hom(kw,1,32,0) + ( hom(kw+1,1,32,0)-hom(kw,1,32,0) ) *   &
3835                           ( ( zv(n) - zw(kw) ) / ( zw(kw+1)-zw(kw) ) )
3836             ENDIF
3837
3838             vv_int = ( 1.0_wp / 3.0_wp ) * ( aa + bb + cc )
3839!
3840!--          Needed to avoid NaN particle velocities. The value of 1.0 is just
3841!--          an educated guess for the given case.
3842             IF ( vv_int + ( 2.0_wp / 3.0_wp ) * e_mean_int == 0.0_wp )  THEN
3843                fs_int(n) = 1.0_wp
3844             ELSE
3845                fs_int(n) = ( 2.0_wp / 3.0_wp ) * e_mean_int /                 &
3846                            ( vv_int + ( 2.0_wp / 3.0_wp ) * e_mean_int )
3847             ENDIF
3848
3849          ENDDO
3850       ENDDO
3851
3852       DO  nb = 0, 7
3853          DO  n = start_index(nb), end_index(nb)
3854             rg(n,1) = random_gauss( iran_part, 5.0_wp )
3855             rg(n,2) = random_gauss( iran_part, 5.0_wp )
3856             rg(n,3) = random_gauss( iran_part, 5.0_wp )
3857          ENDDO
3858       ENDDO
3859
3860       DO  nb = 0, 7
3861          DO  n = start_index(nb), end_index(nb)
3862
3863!
3864!--          Calculate the Lagrangian timescale according to Weil et al. (2004).
3865             lagr_timescale(n) = ( 4.0_wp * e_int(n) + 1E-20_wp ) / &
3866                              ( 3.0_wp * fs_int(n) * c_0 * diss_int(n) + 1E-20_wp )
3867
3868!
3869!--          Calculate the next particle timestep. dt_gap is the time needed to
3870!--          complete the current LES timestep.
3871             dt_gap(n) = dt_3d - particles(n)%dt_sum
3872             dt_particle(n) = MIN( dt_3d, 0.025_wp * lagr_timescale(n), dt_gap(n) )
3873             particles(n)%aux1 = lagr_timescale(n)
3874             particles(n)%aux2 = dt_gap(n)
3875!
3876!--          The particle timestep should not be too small in order to prevent
3877!--          the number of particle timesteps of getting too large
3878             IF ( dt_particle(n) < dt_min_part )  THEN
3879                IF ( dt_min_part < dt_gap(n) )  THEN
3880                   dt_particle(n) = dt_min_part
3881                ELSE
3882                   dt_particle(n) = dt_gap(n)
3883                ENDIF
3884             ENDIF
3885             rvar1_temp(n) = particles(n)%rvar1
3886             rvar2_temp(n) = particles(n)%rvar2
3887             rvar3_temp(n) = particles(n)%rvar3
3888!
3889!--          Calculate the SGS velocity components
3890             IF ( particles(n)%age == 0.0_wp )  THEN
3891!
3892!--             For new particles the SGS components are derived from the SGS
3893!--             TKE. Limit the Gaussian random number to the interval
3894!--             [-5.0*sigma, 5.0*sigma] in order to prevent the SGS velocities
3895!--             from becoming unrealistically large.
3896                rvar1_temp(n) = SQRT( 2.0_wp * sgs_wf_part * e_int(n)          &
3897                                          + 1E-20_wp ) * ( rg(n,1) - 1.0_wp )
3898                rvar2_temp(n) = SQRT( 2.0_wp * sgs_wf_part * e_int(n)          &
3899                                          + 1E-20_wp ) * ( rg(n,2) - 1.0_wp )
3900                rvar3_temp(n) = SQRT( 2.0_wp * sgs_wf_part * e_int(n)          &
3901                                          + 1E-20_wp ) * ( rg(n,3) - 1.0_wp )
3902
3903             ELSE
3904!
3905!--             Restriction of the size of the new timestep: compared to the
3906!--             previous timestep the increase must not exceed 200%. First,
3907!--             check if age > age_m, in order to prevent that particles get zero
3908!--             timestep.
3909                dt_particle_m = MERGE( dt_particle(n),                         &
3910                                       particles(n)%age - particles(n)%age_m,  &
3911                                       particles(n)%age - particles(n)%age_m < &
3912                                       1E-8_wp )
3913                IF ( dt_particle(n) > 2.0_wp * dt_particle_m )  THEN
3914                   dt_particle(n) = 2.0_wp * dt_particle_m
3915                ENDIF
3916
3917!--             For old particles the SGS components are correlated with the
3918!--             values from the previous timestep. Random numbers have also to
3919!--             be limited (see above).
3920!--             As negative values for the subgrid TKE are not allowed, the
3921!--             change of the subgrid TKE with time cannot be smaller than
3922!--             -e_int(n)/dt_particle. This value is used as a lower boundary
3923!--             value for the change of TKE
3924                de_dt_min = - e_int(n) / dt_particle(n)
3925
3926                de_dt = ( e_int(n) - particles(n)%e_m ) / dt_particle_m
3927
3928                IF ( de_dt < de_dt_min )  THEN
3929                   de_dt = de_dt_min
3930                ENDIF
3931
3932                CALL weil_stochastic_eq(rvar1_temp(n), fs_int(n), e_int(n),& 
3933                                        de_dx_int(n), de_dt, diss_int(n),       &
3934                                        dt_particle(n), rg(n,1), term_1_2(n) )
3935
3936                CALL weil_stochastic_eq(rvar2_temp(n), fs_int(n), e_int(n),& 
3937                                        de_dy_int(n), de_dt, diss_int(n),       &
3938                                        dt_particle(n), rg(n,2), term_1_2(n) )
3939
3940                CALL weil_stochastic_eq(rvar3_temp(n), fs_int(n), e_int(n),& 
3941                                        de_dz_int(n), de_dt, diss_int(n),       &
3942                                        dt_particle(n), rg(n,3), term_1_2(n) )
3943
3944             ENDIF
3945
3946          ENDDO
3947       ENDDO
3948!
3949!--    Check if the added SGS velocities result in a violation of the CFL-
3950!--    criterion. If yes choose a smaller timestep based on the new velocities
3951!--    and calculate SGS velocities again
3952       dz_temp = zw(kp)-zw(kp-1)
3953
3954       DO  nb = 0, 7
3955          DO  n = start_index(nb), end_index(nb)
3956             IF ( .NOT. particles(n)%age == 0.0_wp .AND.                       &
3957                (ABS( u_int(n) + rvar1_temp(n) ) > (dx/dt_particle(n))  .OR.   &
3958                 ABS( v_int(n) + rvar2_temp(n) ) > (dy/dt_particle(n))  .OR.   &
3959                 ABS( w_int(n) + rvar3_temp(n) ) > (dz_temp/dt_particle(n)))) THEN
3960
3961                dt_particle(n) = 0.9_wp * MIN(                                 &
3962                                 ( dx / ABS( u_int(n) + rvar1_temp(n) ) ),     &
3963                                 ( dy / ABS( v_int(n) + rvar2_temp(n) ) ),     &
3964                                 ( dz_temp / ABS( w_int(n) + rvar3_temp(n) ) ) )
3965
3966!
3967!--             Reset temporary SGS velocites to "current" ones
3968                rvar1_temp(n) = particles(n)%rvar1
3969                rvar2_temp(n) = particles(n)%rvar2
3970                rvar3_temp(n) = particles(n)%rvar3
3971
3972                de_dt_min = - e_int(n) / dt_particle(n)
3973
3974                de_dt = ( e_int(n) - particles(n)%e_m ) / dt_particle_m
3975
3976                IF ( de_dt < de_dt_min )  THEN
3977                   de_dt = de_dt_min
3978                ENDIF
3979
3980                CALL weil_stochastic_eq(rvar1_temp(n), fs_int(n), e_int(n),& 
3981                                        de_dx_int(n), de_dt, diss_int(n),       &
3982                                        dt_particle(n), rg(n,1), term_1_2(n) )
3983
3984                CALL weil_stochastic_eq(rvar2_temp(n), fs_int(n), e_int(n),& 
3985                                        de_dy_int(n), de_dt, diss_int(n),       &
3986                                        dt_particle(n), rg(n,2), term_1_2(n) )
3987
3988                CALL weil_stochastic_eq(rvar3_temp(n), fs_int(n), e_int(n),& 
3989                                        de_dz_int(n), de_dt, diss_int(n),       &
3990                                        dt_particle(n), rg(n,3), term_1_2(n) )
3991             ENDIF
3992
3993!
3994!--          Update particle velocites
3995             particles(n)%rvar1 = rvar1_temp(n)
3996             particles(n)%rvar2 = rvar2_temp(n)
3997             particles(n)%rvar3 = rvar3_temp(n)
3998             u_int(n) = u_int(n) + particles(n)%rvar1
3999             v_int(n) = v_int(n) + particles(n)%rvar2
4000             w_int(n) = w_int(n) + particles(n)%rvar3
4001!
4002!--          Store the SGS TKE of the current timelevel which is needed for
4003!--          for calculating the SGS particle velocities at the next timestep
4004             particles(n)%e_m = e_int(n)
4005          ENDDO
4006       ENDDO
4007
4008    ELSE
4009!
4010!--    If no SGS velocities are used, only the particle timestep has to
4011!--    be set
4012       dt_particle = dt_3d
4013
4014    ENDIF
4015
4016    dens_ratio = particle_groups(particles(1:number_of_particles)%group)%density_ratio
4017    IF ( ANY( dens_ratio == 0.0_wp ) )  THEN
4018!
4019!--    Decide whether the particle loop runs over the subboxes or only over 1,
4020!--    number_of_particles. This depends on the selected interpolation method.
4021!--    If particle interpolation method is not trilinear, then the sorting within
4022!--    subboxes is not required. However, therefore the index start_index(nb) and
4023!--    end_index(nb) are not defined and the loops are still over
4024!--    number_of_particles. @todo find a more generic way to write this loop or
4025!--    delete trilinear interpolation
4026       IF ( TRIM(particle_interpolation)  ==  'trilinear' )  THEN
4027          subbox_start = 0
4028          subbox_end   = 7
4029       ELSE
4030          subbox_start = 1
4031          subbox_end   = 1
4032       ENDIF
4033!
4034!--    loop over subboxes. In case of simple interpolation scheme no subboxes
4035!--    are introduced, as they are not required. Accordingly, this loops goes
4036!--    from 1 to 1.
4037       DO  nb = subbox_start, subbox_end
4038          IF ( TRIM(particle_interpolation)  ==  'trilinear' )  THEN
4039             particle_start = start_index(nb)
4040             particle_end   = end_index(nb)
4041          ELSE
4042             particle_start = 1
4043             particle_end   = number_of_particles
4044          ENDIF
4045!
4046!--         Loop from particle start to particle end
4047            DO  n = particle_start, particle_end
4048
4049!
4050!--          Particle advection
4051             IF ( dens_ratio(n) == 0.0_wp )  THEN
4052!
4053!--             Pure passive transport (without particle inertia)
4054                particles(n)%x = xv(n) + u_int(n) * dt_particle(n)
4055                particles(n)%y = yv(n) + v_int(n) * dt_particle(n)
4056                particles(n)%z = zv(n) + w_int(n) * dt_particle(n)
4057
4058                particles(n)%speed_x = u_int(n)
4059                particles(n)%speed_y = v_int(n)
4060                particles(n)%speed_z = w_int(n)
4061
4062             ELSE
4063!
4064!--             Transport of particles with inertia
4065                particles(n)%x = particles(n)%x + particles(n)%speed_x * &
4066                                                  dt_particle(n)
4067                particles(n)%y = particles(n)%y + particles(n)%speed_y * &
4068                                                  dt_particle(n)
4069                particles(n)%z = particles(n)%z + particles(n)%speed_z * &
4070                                                  dt_particle(n)
4071
4072!
4073!--             Update of the particle velocity
4074                IF ( cloud_droplets )  THEN
4075!
4076!--                Terminal velocity is computed for vertical direction (Rogers et
4077!--                al., 1993, J. Appl. Meteorol.)
4078                   diameter = particles(n)%radius * 2000.0_wp !diameter in mm
4079                   IF ( diameter <= d0_rog )  THEN
4080                      w_s = k_cap_rog * diameter * ( 1.0_wp - EXP( -k_low_rog * diameter ) )
4081                   ELSE
4082                      w_s = a_rog - b_rog * EXP( -c_rog * diameter )
4083                   ENDIF
4084
4085!
4086!--                If selected, add random velocities following Soelch and Kaercher
4087!--                (2010, Q. J. R. Meteorol. Soc.)
4088                   IF ( use_sgs_for_particles )  THEN
4089                      lagr_timescale(n) = km(kp,jp,ip) / MAX( e(kp,jp,ip), 1.0E-20_wp )
4090                      RL             = EXP( -1.0_wp * dt_3d / MAX( lagr_timescale(n), &
4091                                             1.0E-20_wp ) )
4092                      sigma          = SQRT( e(kp,jp,ip) )
4093
4094                      rg1 = random_gauss( iran_part, 5.0_wp ) - 1.0_wp
4095                      rg2 = random_gauss( iran_part, 5.0_wp ) - 1.0_wp
4096                      rg3 = random_gauss( iran_part, 5.0_wp ) - 1.0_wp
4097
4098                      particles(n)%rvar1 = RL * particles(n)%rvar1 +              &
4099                                           SQRT( 1.0_wp - RL**2 ) * sigma * rg1
4100                      particles(n)%rvar2 = RL * particles(n)%rvar2 +              &
4101                                           SQRT( 1.0_wp - RL**2 ) * sigma * rg2
4102                      particles(n)%rvar3 = RL * particles(n)%rvar3 +              &
4103                                           SQRT( 1.0_wp - RL**2 ) * sigma * rg3
4104
4105                      particles(n)%speed_x = u_int(n) + particles(n)%rvar1
4106                      particles(n)%speed_y = v_int(n) + particles(n)%rvar2
4107                      particles(n)%speed_z = w_int(n) + particles(n)%rvar3 - w_s
4108                   ELSE
4109                      particles(n)%speed_x = u_int(n)
4110                      particles(n)%speed_y = v_int(n)
4111                      particles(n)%speed_z = w_int(n) - w_s
4112                   ENDIF
4113
4114                ELSE
4115
4116                   IF ( use_sgs_for_particles )  THEN
4117                      exp_arg  = particle_groups(particles(n)%group)%exp_arg
4118                      exp_term = EXP( -exp_arg * dt_particle(n) )
4119                   ELSE
4120                      exp_arg  = particle_groups(particles(n)%group)%exp_arg
4121                      exp_term = particle_groups(particles(n)%group)%exp_term
4122                   ENDIF
4123                   particles(n)%speed_x = particles(n)%speed_x * exp_term +         &
4124                                          u_int(n) * ( 1.0_wp - exp_term )
4125                   particles(n)%speed_y = particles(n)%speed_y * exp_term +         &
4126                                          v_int(n) * ( 1.0_wp - exp_term )
4127                   particles(n)%speed_z = particles(n)%speed_z * exp_term +         &
4128                                          ( w_int(n) - ( 1.0_wp - dens_ratio(n) ) * &
4129                                          g / exp_arg ) * ( 1.0_wp - exp_term )
4130                ENDIF
4131
4132             ENDIF
4133          ENDDO
4134       ENDDO
4135
4136    ELSE
4137!
4138!--    Decide whether the particle loop runs over the subboxes or only over 1,
4139!--    number_of_particles. This depends on the selected interpolation method.
4140       IF ( TRIM(particle_interpolation)  ==  'trilinear' )  THEN
4141          subbox_start = 0
4142          subbox_end   = 7
4143       ELSE
4144          subbox_start = 1
4145          subbox_end   = 1
4146       ENDIF
4147!--    loop over subboxes. In case of simple interpolation scheme no subboxes
4148!--    are introduced, as they are not required. Accordingly, this loops goes
4149!--    from 1 to 1.
4150       DO  nb = subbox_start, subbox_end
4151          IF ( TRIM(particle_interpolation)  ==  'trilinear' )  THEN
4152             particle_start = start_index(nb)
4153             particle_end   = end_index(nb)
4154          ELSE
4155             particle_start = 1
4156             particle_end   = number_of_particles
4157          ENDIF
4158!
4159!--         Loop from particle start to particle end
4160            DO  n = particle_start, particle_end
4161
4162!
4163!--          Transport of particles with inertia
4164             particles(n)%x = xv(n) + particles(n)%speed_x * dt_particle(n)
4165             particles(n)%y = yv(n) + particles(n)%speed_y * dt_particle(n)
4166             particles(n)%z = zv(n) + particles(n)%speed_z * dt_particle(n)
4167!
4168!--          Update of the particle velocity
4169             IF ( cloud_droplets )  THEN
4170!
4171!--             Terminal velocity is computed for vertical direction (Rogers et al.,
4172!--             1993, J. Appl. Meteorol.)
4173                diameter = particles(n)%radius * 2000.0_wp !diameter in mm
4174                IF ( diameter <= d0_rog )  THEN
4175                   w_s = k_cap_rog * diameter * ( 1.0_wp - EXP( -k_low_rog * diameter ) )
4176                ELSE
4177                   w_s = a_rog - b_rog * EXP( -c_rog * diameter )
4178                ENDIF
4179
4180!
4181!--             If selected, add random velocities following Soelch and Kaercher
4182!--             (2010, Q. J. R. Meteorol. Soc.)
4183                IF ( use_sgs_for_particles )  THEN
4184                    lagr_timescale(n) = km(kp,jp,ip) / MAX( e(kp,jp,ip), 1.0E-20_wp )
4185                     RL             = EXP( -1.0_wp * dt_3d / MAX( lagr_timescale(n), &
4186                                             1.0E-20_wp ) )
4187                    sigma          = SQRT( e(kp,jp,ip) )
4188
4189                    rg1 = random_gauss( iran_part, 5.0_wp ) - 1.0_wp
4190                    rg2 = random_gauss( iran_part, 5.0_wp ) - 1.0_wp
4191                    rg3 = random_gauss( iran_part, 5.0_wp ) - 1.0_wp
4192
4193                    particles(n)%rvar1 = RL * particles(n)%rvar1 +                &
4194                                         SQRT( 1.0_wp - RL**2 ) * sigma * rg1
4195                    particles(n)%rvar2 = RL * particles(n)%rvar2 +                &
4196                                         SQRT( 1.0_wp - RL**2 ) * sigma * rg2
4197                    particles(n)%rvar3 = RL * particles(n)%rvar3 +                &
4198                                         SQRT( 1.0_wp - RL**2 ) * sigma * rg3
4199
4200                    particles(n)%speed_x = u_int(n) + particles(n)%rvar1
4201                    particles(n)%speed_y = v_int(n) + particles(n)%rvar2
4202                    particles(n)%speed_z = w_int(n) + particles(n)%rvar3 - w_s
4203                ELSE
4204                    particles(n)%speed_x = u_int(n)
4205                    particles(n)%speed_y = v_int(n)
4206                    particles(n)%speed_z = w_int(n) - w_s
4207                ENDIF
4208
4209             ELSE
4210
4211                IF ( use_sgs_for_particles )  THEN
4212                   exp_arg  = particle_groups(particles(n)%group)%exp_arg
4213                   exp_term = EXP( -exp_arg * dt_particle(n) )
4214                ELSE
4215                   exp_arg  = particle_groups(particles(n)%group)%exp_arg
4216                   exp_term = particle_groups(particles(n)%group)%exp_term
4217                ENDIF
4218                particles(n)%speed_x = particles(n)%speed_x * exp_term +             &
4219                                       u_int(n) * ( 1.0_wp - exp_term )
4220                particles(n)%speed_y = particles(n)%speed_y * exp_term +             &
4221                                       v_int(n) * ( 1.0_wp - exp_term )
4222                particles(n)%speed_z = particles(n)%speed_z * exp_term +             &
4223                                       ( w_int(n) - ( 1.0_wp - dens_ratio(n) ) * g / &
4224                                       exp_arg ) * ( 1.0_wp - exp_term )
4225             ENDIF
4226          ENDDO
4227       ENDDO
4228
4229    ENDIF
4230
4231!
4232!-- Store the old age of the particle ( needed to prevent that a
4233!-- particle crosses several PEs during one timestep, and for the
4234!-- evaluation of the subgrid particle velocity fluctuations )
4235    particles(1:number_of_particles)%age_m = particles(1:number_of_particles)%age
4236
4237!
4238!--    loop over subboxes. In case of simple interpolation scheme no subboxes
4239!--    are introduced, as they are not required. Accordingly, this loops goes
4240!--    from 1 to 1.
4241!
4242!-- Decide whether the particle loop runs over the subboxes or only over 1,
4243!-- number_of_particles. This depends on the selected interpolation method.
4244    IF ( TRIM(particle_interpolation)  ==  'trilinear' )  THEN
4245       subbox_start = 0
4246       subbox_end   = 7
4247    ELSE
4248       subbox_start = 1
4249       subbox_end   = 1
4250    ENDIF
4251    DO  nb = subbox_start, subbox_end
4252       IF ( TRIM(particle_interpolation)  ==  'trilinear' )  THEN
4253          particle_start = start_index(nb)
4254          particle_end   = end_index(nb)
4255       ELSE
4256          particle_start = 1
4257          particle_end   = number_of_particles
4258       ENDIF
4259!
4260!--    Loop from particle start to particle end
4261       DO  n = particle_start, particle_end
4262!
4263!--       Increment the particle age and the total time that the particle
4264!--       has advanced within the particle timestep procedure
4265          particles(n)%age    = particles(n)%age    + dt_particle(n)
4266          particles(n)%dt_sum = particles(n)%dt_sum + dt_particle(n)
4267
4268!
4269!--       Check whether there is still a particle that has not yet completed
4270!--       the total LES timestep
4271          IF ( ( dt_3d - particles(n)%dt_sum ) > 1E-8_wp )  THEN
4272             dt_3d_reached_l = .FALSE.
4273          ENDIF
4274
4275       ENDDO
4276    ENDDO
4277
4278    CALL cpu_log( log_point_s(44), 'lpm_advec', 'pause' )
4279
4280
4281 END SUBROUTINE lpm_advec
4282
4283 
4284!------------------------------------------------------------------------------! 
4285! Description:
4286! ------------
4287!> Calculation of subgrid-scale particle speed using the stochastic model
4288!> of Weil et al. (2004, JAS, 61, 2877-2887).
4289!------------------------------------------------------------------------------!
4290 SUBROUTINE weil_stochastic_eq( v_sgs, fs_n, e_n, dedxi_n, dedt_n, diss_n,     &
4291                                dt_n, rg_n, fac )
4292
4293    REAL(wp) ::  a1      !< dummy argument
4294    REAL(wp) ::  dedt_n  !< time derivative of TKE at particle position
4295    REAL(wp) ::  dedxi_n !< horizontal derivative of TKE at particle position
4296    REAL(wp) ::  diss_n  !< dissipation at particle position
4297    REAL(wp) ::  dt_n    !< particle timestep
4298    REAL(wp) ::  e_n     !< TKE at particle position
4299    REAL(wp) ::  fac     !< flag to identify adjacent topography
4300    REAL(wp) ::  fs_n    !< weighting factor to prevent that subgrid-scale particle speed becomes too large
4301    REAL(wp) ::  rg_n    !< random number
4302    REAL(wp) ::  term1   !< memory term
4303    REAL(wp) ::  term2   !< drift correction term
4304    REAL(wp) ::  term3   !< random term
4305    REAL(wp) ::  v_sgs   !< subgrid-scale velocity component
4306
4307!-- At first, limit TKE to a small non-zero number, in order to prevent
4308!-- the occurrence of extremely large SGS-velocities in case TKE is zero,
4309!-- (could occur at the simulation begin).
4310    e_n = MAX( e_n, 1E-20_wp )
4311!
4312!-- Please note, terms 1 and 2 (drift and memory term, respectively) are
4313!-- multiplied by a flag to switch of both terms near topography.
4314!-- This is necessary, as both terms may cause a subgrid-scale velocity build up
4315!-- if particles are trapped in regions with very small TKE, e.g. in narrow street
4316!-- canyons resolved by only a few grid points. Hence, term 1 and term 2 are
4317!-- disabled if one of the adjacent grid points belongs to topography.
4318!-- Moreover, in this case, the  previous subgrid-scale component is also set
4319!-- to zero.
4320
4321    a1 = fs_n * c_0 * diss_n
4322!
4323!-- Memory term
4324    term1 = - a1 * v_sgs * dt_n / ( 4.0_wp * sgs_wf_part * e_n + 1E-20_wp )    &
4325                 * fac
4326!
4327!-- Drift correction term
4328    term2 = ( ( dedt_n * v_sgs / e_n ) + dedxi_n ) * 0.5_wp * dt_n              &
4329                 * fac
4330!
4331!-- Random term
4332    term3 = SQRT( MAX( a1, 1E-20_wp ) ) * ( rg_n - 1.0_wp ) * SQRT( dt_n )
4333!
4334!-- In cese one of the adjacent grid-boxes belongs to topograhy, the previous
4335!-- subgrid-scale velocity component is set to zero, in order to prevent a
4336!-- velocity build-up.
4337!-- This case, set also previous subgrid-scale component to zero.
4338    v_sgs = v_sgs * fac + term1 + term2 + term3
4339
4340 END SUBROUTINE weil_stochastic_eq 
4341 
4342 
4343!------------------------------------------------------------------------------! 
4344! Description:
4345! ------------
4346!> Boundary conditions for the Lagrangian particles.
4347!> The routine consists of two different parts. One handles the bottom (flat)
4348!> and top boundary. In this part, also particles which exceeded their lifetime
4349!> are deleted.
4350!> The other part handles the reflection of particles from vertical walls.
4351!> This part was developed by Jin Zhang during 2006-2007.
4352!>
4353!> To do: Code structure for finding the t_index values and for checking the
4354!> -----  reflection conditions is basically the same for all four cases, so it
4355!>        should be possible to further simplify/shorten it.
4356!>
4357!> THE WALLS PART OF THIS ROUTINE HAS NOT BEEN TESTED FOR OCEAN RUNS SO FAR!!!!
4358!> (see offset_ocean_*)
4359!------------------------------------------------------------------------------!
4360 SUBROUTINE lpm_boundary_conds( location_bc , i, j, k )
4361
4362    CHARACTER (LEN=*), INTENT(IN) ::  location_bc !< general mode: boundary conditions at bottom/top of the model domain
4363                                   !< or at vertical surfaces (buildings, terrain steps)   
4364    INTEGER(iwp), INTENT(IN) ::  i !< grid index of particle box along x
4365    INTEGER(iwp), INTENT(IN) ::  j !< grid index of particle box along y
4366    INTEGER(iwp), INTENT(IN) ::  k !< grid index of particle box along z
4367
4368    INTEGER(iwp) ::  inc            !< dummy for sorting algorithmus
4369    INTEGER(iwp) ::  ir             !< dummy for sorting algorithmus
4370    INTEGER(iwp) ::  i1             !< grid index (x) of old particle position
4371    INTEGER(iwp) ::  i2             !< grid index (x) of current particle position
4372    INTEGER(iwp) ::  i3             !< grid index (x) of intermediate particle position
4373    INTEGER(iwp) ::  jr             !< dummy for sorting algorithmus
4374    INTEGER(iwp) ::  j1             !< grid index (y) of old particle position
4375    INTEGER(iwp) ::  j2             !< grid index (y) of current particle position
4376    INTEGER(iwp) ::  j3             !< grid index (y) of intermediate particle position
4377    INTEGER(iwp) ::  k1             !< grid index (z) of old particle position
4378    INTEGER(iwp) ::  k2             !< grid index (z) of current particle position
4379    INTEGER(iwp) ::  k3             !< grid index (z) of intermediate particle position
4380    INTEGER(iwp) ::  n              !< particle number
4381    INTEGER(iwp) ::  t_index        !< running index for intermediate particle timesteps in reflection algorithmus
4382    INTEGER(iwp) ::  t_index_number !< number of intermediate particle timesteps in reflection algorithmus
4383    INTEGER(iwp) ::  tmp_x          !< dummy for sorting algorithm
4384    INTEGER(iwp) ::  tmp_y          !< dummy for sorting algorithm
4385    INTEGER(iwp) ::  tmp_z          !< dummy for sorting algorithm
4386
4387    INTEGER(iwp), DIMENSION(0:10) :: x_ind(0:10) = 0 !< index array (x) of intermediate particle positions
4388    INTEGER(iwp), DIMENSION(0:10) :: y_ind(0:10) = 0 !< index array (y) of intermediate particle positions
4389    INTEGER(iwp), DIMENSION(0:10) :: z_ind(0:10) = 0 !< index array (z) of intermediate particle positions
4390
4391    LOGICAL  ::  cross_wall_x    !< flag to check if particle reflection along x is necessary
4392    LOGICAL  ::  cross_wall_y    !< flag to check if particle reflection along y is necessary
4393    LOGICAL  ::  cross_wall_z    !< flag to check if particle reflection along z is necessary
4394    LOGICAL  ::  reflect_x       !< flag to check if particle is already reflected along x
4395    LOGICAL  ::  reflect_y       !< flag to check if particle is already reflected along y
4396    LOGICAL  ::  reflect_z       !< flag to check if particle is already reflected along z
4397    LOGICAL  ::  tmp_reach_x     !< dummy for sorting algorithmus
4398    LOGICAL  ::  tmp_reach_y     !< dummy for sorting algorithmus
4399    LOGICAL  ::  tmp_reach_z     !< dummy for sorting algorithmus
4400    LOGICAL  ::  x_wall_reached  !< flag to check if particle has already reached wall
4401    LOGICAL  ::  y_wall_reached  !< flag to check if particle has already reached wall
4402    LOGICAL  ::  z_wall_reached  !< flag to check if particle has already reached wall
4403
4404    LOGICAL, DIMENSION(0:10) ::  reach_x  !< flag to check if particle is at a yz-wall
4405    LOGICAL, DIMENSION(0:10) ::  reach_y  !< flag to check if particle is at a xz-wall
4406    LOGICAL, DIMENSION(0:10) ::  reach_z  !< flag to check if particle is at a xy-wall
4407
4408    REAL(wp) ::  dt_particle    !< particle timestep
4409    REAL(wp) ::  eps = 1E-10_wp !< security number to check if particle has reached a wall
4410    REAL(wp) ::  pos_x          !< intermediate particle position (x)
4411    REAL(wp) ::  pos_x_old      !< particle position (x) at previous particle timestep
4412    REAL(wp) ::  pos_y          !< intermediate particle position (y)
4413    REAL(wp) ::  pos_y_old      !< particle position (y) at previous particle timestep
4414    REAL(wp) ::  pos_z          !< intermediate particle position (z)
4415    REAL(wp) ::  pos_z_old      !< particle position (z) at previous particle timestep
4416    REAL(wp) ::  prt_x          !< current particle position (x)
4417    REAL(wp) ::  prt_y          !< current particle position (y)
4418    REAL(wp) ::  prt_z          !< current particle position (z)
4419    REAL(wp) ::  t_old          !< previous reflection time
4420    REAL(wp) ::  tmp_t          !< dummy for sorting algorithmus
4421    REAL(wp) ::  xwall          !< location of wall in x
4422    REAL(wp) ::  ywall          !< location of wall in y
4423    REAL(wp) ::  zwall          !< location of wall in z
4424
4425    REAL(wp), DIMENSION(0:10) ::  t  !< reflection time
4426
4427    SELECT CASE ( location_bc )
4428
4429       CASE ( 'bottom/top' )
4430
4431!
4432!--    Apply boundary conditions to those particles that have crossed the top or
4433!--    bottom boundary and delete those particles, which are older than allowed
4434       DO  n = 1, number_of_particles
4435
4436!
4437!--       Stop if particles have moved further than the length of one
4438!--       PE subdomain (newly released particles have age = age_m!)
4439          IF ( particles(n)%age /= particles(n)%age_m )  THEN
4440             IF ( ABS(particles(n)%speed_x) >                                  &
4441                  ((nxr-nxl+2)*dx)/(particles(n)%age-particles(n)%age_m)  .OR. &
4442                  ABS(particles(n)%speed_y) >                                  &
4443                  ((nyn-nys+2)*dy)/(particles(n)%age-particles(n)%age_m) )  THEN
4444
4445                  WRITE( message_string, * )  'particle too fast.  n = ',  n 
4446                  CALL message( 'lpm_boundary_conds', 'PA0148', 2, 2, -1, 6, 1 )
4447             ENDIF
4448          ENDIF
4449
4450          IF ( particles(n)%age > particle_maximum_age  .AND.  &
4451               particles(n)%particle_mask )                              &
4452          THEN
4453             particles(n)%particle_mask  = .FALSE.
4454             deleted_particles = deleted_particles + 1
4455          ENDIF
4456
4457          IF ( particles(n)%z >= zw(nz)  .AND.  particles(n)%particle_mask )  THEN
4458             IF ( ibc_par_t == 1 )  THEN
4459!
4460!--             Particle absorption
4461                particles(n)%particle_mask  = .FALSE.
4462                deleted_particles = deleted_particles + 1
4463             ELSEIF ( ibc_par_t == 2 )  THEN
4464!
4465!--             Particle reflection
4466                particles(n)%z       = 2.0_wp * zw(nz) - particles(n)%z
4467                particles(n)%speed_z = -particles(n)%speed_z
4468                IF ( use_sgs_for_particles  .AND. &
4469                     particles(n)%rvar3 > 0.0_wp )  THEN
4470                   particles(n)%rvar3 = -particles(n)%rvar3
4471                ENDIF
4472             ENDIF
4473          ENDIF
4474
4475          IF ( particles(n)%z < zw(0)  .AND.  particles(n)%particle_mask )  THEN
4476             IF ( ibc_par_b == 1 )  THEN
4477!
4478!--             Particle absorption
4479                particles(n)%particle_mask  = .FALSE.
4480                deleted_particles = deleted_particles + 1
4481             ELSEIF ( ibc_par_b == 2 )  THEN
4482!
4483!--             Particle reflection
4484                particles(n)%z       = 2.0_wp * zw(0) - particles(n)%z
4485                particles(n)%speed_z = -particles(n)%speed_z
4486                IF ( use_sgs_for_particles  .AND. &
4487                     particles(n)%rvar3 < 0.0_wp )  THEN
4488                   particles(n)%rvar3 = -particles(n)%rvar3
4489                ENDIF
4490             ENDIF
4491          ENDIF
4492       ENDDO
4493
4494      CASE ( 'walls' )
4495
4496       CALL cpu_log( log_point_s(48), 'lpm_wall_reflect', 'start' )
4497
4498       DO  n = 1, number_of_particles
4499!
4500!--       Recalculate particle timestep
4501          dt_particle = particles(n)%age - particles(n)%age_m
4502!
4503!--       Obtain x/y indices for current particle position
4504          i2 = particles(n)%x * ddx
4505          j2 = particles(n)%y * ddy
4506          IF (zw(k)   < particles(n)%z ) k2 = k + 1
4507          IF (zw(k)   > particles(n)%z .AND. zw(k-1) < particles(n)%z ) k2 = k
4508          IF (zw(k-1) > particles(n)%z ) k2 = k - 1 
4509!
4510!--       Save current particle positions
4511          prt_x = particles(n)%x
4512          prt_y = particles(n)%y
4513          prt_z = particles(n)%z
4514!
4515!--       Recalculate old particle positions
4516          pos_x_old = particles(n)%x - particles(n)%speed_x * dt_particle
4517          pos_y_old = particles(n)%y - particles(n)%speed_y * dt_particle
4518          pos_z_old = particles(n)%z - particles(n)%speed_z * dt_particle
4519!
4520!--       Obtain x/y indices for old particle positions
4521          i1 = i
4522          j1 = j
4523          k1 = k
4524!
4525!--       Determine horizontal as well as vertical walls at which particle can
4526!--       be potentially reflected.
4527!--       Start with walls aligned in yz layer.
4528!--       Wall to the right
4529          IF ( prt_x > pos_x_old )  THEN
4530             xwall = ( i1 + 1 ) * dx
4531!
4532!--       Wall to the left
4533          ELSE
4534             xwall = i1 * dx
4535          ENDIF
4536!
4537!--       Walls aligned in xz layer
4538!--       Wall to the north
4539          IF ( prt_y > pos_y_old )  THEN
4540             ywall = ( j1 +1 ) * dy
4541!--       Wall to the south
4542          ELSE
4543             ywall = j1 * dy
4544          ENDIF
4545
4546          IF ( prt_z > pos_z_old ) THEN
4547             zwall = zw(k)
4548          ELSE
4549             zwall = zw(k-1)
4550          ENDIF
4551!
4552!--       Initialize flags to check if particle reflection is necessary
4553          cross_wall_x = .FALSE.
4554          cross_wall_y = .FALSE.
4555          cross_wall_z = .FALSE.
4556!
4557!--       Initialize flags to check if a wall is reached
4558          reach_x      = .FALSE.
4559          reach_y      = .FALSE.
4560          reach_z      = .FALSE.
4561!
4562!--       Initialize flags to check if a particle was already reflected
4563          reflect_x    = .FALSE.
4564          reflect_y    = .FALSE.
4565          reflect_z    = .FALSE.
4566!
4567!--       Initialize flags to check if a wall is already crossed.
4568!--       ( Required to obtain correct indices. )
4569          x_wall_reached = .FALSE.
4570          y_wall_reached = .FALSE.
4571          z_wall_reached = .FALSE.
4572!
4573!--       Initialize time array
4574          t     = 0.0_wp
4575!
4576!--       Check if particle can reach any wall. This case, calculate the
4577!--       fractional time needed to reach this wall. Store this fractional
4578!--       timestep in array t. Moreover, store indices for these grid
4579!--       boxes where the respective wall belongs to. 
4580!--       Start with x-direction.
4581          t_index    = 1
4582          t(t_index) = ( xwall - pos_x_old )                                   &
4583                     / MERGE( MAX( prt_x - pos_x_old,  1E-30_wp ),             &
4584                              MIN( prt_x - pos_x_old, -1E-30_wp ),             &
4585                              prt_x > pos_x_old )
4586          x_ind(t_index)   = i2
4587          y_ind(t_index)   = j1
4588          z_ind(t_index)   = k1
4589          reach_x(t_index) = .TRUE.
4590          reach_y(t_index) = .FALSE.
4591          reach_z(t_index) = .FALSE.
4592!
4593!--       Store these values only if particle really reaches any wall. t must
4594!--       be in a interval between [0:1].
4595          IF ( t(t_index) <= 1.0_wp .AND. t(t_index) >= 0.0_wp )  THEN
4596             t_index      = t_index + 1
4597             cross_wall_x = .TRUE.
4598          ENDIF
4599!
4600!--       y-direction
4601          t(t_index) = ( ywall - pos_y_old )                                   &
4602                     / MERGE( MAX( prt_y - pos_y_old,  1E-30_wp ),             &
4603                              MIN( prt_y - pos_y_old, -1E-30_wp ),             &
4604                              prt_y > pos_y_old )
4605          x_ind(t_index)   = i1
4606          y_ind(t_index)   = j2
4607          z_ind(t_index)   = k1
4608          reach_x(t_index) = .FALSE.
4609          reach_y(t_index) = .TRUE.
4610          reach_z(t_index) = .FALSE.
4611          IF ( t(t_index) <= 1.0_wp .AND. t(t_index) >= 0.0_wp )  THEN
4612             t_index      = t_index + 1
4613             cross_wall_y = .TRUE.
4614          ENDIF
4615!
4616!--       z-direction
4617          t(t_index) = (zwall - pos_z_old )                                    &
4618                     / MERGE( MAX( prt_z - pos_z_old,  1E-30_wp ),             &
4619                              MIN( prt_z - pos_z_old, -1E-30_wp ),             &
4620                              prt_z > pos_z_old )
4621
4622          x_ind(t_index)   = i1
4623          y_ind(t_index)   = j1
4624          z_ind(t_index)   = k2
4625          reach_x(t_index) = .FALSE.
4626          reach_y(t_index) = .FALSE.
4627          reach_z(t_index) = .TRUE.
4628          IF( t(t_index) <= 1.0_wp .AND. t(t_index) >= 0.0_wp) THEN
4629             t_index      = t_index + 1
4630             cross_wall_z = .TRUE.
4631          ENDIF
4632
4633          t_index_number = t_index - 1
4634!
4635!--       Carry out reflection only if particle reaches any wall
4636          IF ( cross_wall_x .OR. cross_wall_y .OR. cross_wall_z )  THEN
4637!
4638!--          Sort fractional timesteps in ascending order. Also sort the
4639!--          corresponding indices and flag according to the time interval a 
4640!--          particle reaches the respective wall.
4641             inc = 1
4642             jr  = 1
4643             DO WHILE ( inc <= t_index_number )
4644                inc = 3 * inc + 1
4645             ENDDO
4646
4647             DO WHILE ( inc > 1 )
4648                inc = inc / 3
4649                DO  ir = inc+1, t_index_number
4650                   tmp_t       = t(ir)
4651                   tmp_x       = x_ind(ir)
4652                   tmp_y       = y_ind(ir)
4653                   tmp_z       = z_ind(ir)
4654                   tmp_reach_x = reach_x(ir)
4655                   tmp_reach_y = reach_y(ir)
4656                   tmp_reach_z = reach_z(ir)
4657                   jr    = ir
4658                   DO WHILE ( t(jr-inc) > tmp_t )
4659                      t(jr)       = t(jr-inc)
4660                      x_ind(jr)   = x_ind(jr-inc)
4661                      y_ind(jr)   = y_ind(jr-inc)
4662                      z_ind(jr)   = z_ind(jr-inc)
4663                      reach_x(jr) = reach_x(jr-inc)
4664                      reach_y(jr) = reach_y(jr-inc)
4665                      reach_z(jr) = reach_z(jr-inc)
4666                      jr    = jr - inc
4667                      IF ( jr <= inc )  EXIT
4668                   ENDDO
4669                   t(jr)       = tmp_t
4670                   x_ind(jr)   = tmp_x
4671                   y_ind(jr)   = tmp_y
4672                   z_ind(jr)   = tmp_z
4673                   reach_x(jr) = tmp_reach_x
4674                   reach_y(jr) = tmp_reach_y
4675                   reach_z(jr) = tmp_reach_z
4676                ENDDO
4677             ENDDO
4678!
4679!--          Initialize temporary particle positions
4680             pos_x = pos_x_old
4681             pos_y = pos_y_old
4682             pos_z = pos_z_old
4683!
4684!--          Loop over all times a particle possibly moves into a new grid box
4685             t_old = 0.0_wp
4686             DO t_index = 1, t_index_number 
4687!
4688!--             Calculate intermediate particle position according to the
4689!--             timesteps a particle reaches any wall.
4690                pos_x = pos_x + ( t(t_index) - t_old ) * dt_particle           &
4691                                                       * particles(n)%speed_x
4692                pos_y = pos_y + ( t(t_index) - t_old ) * dt_particle           &
4693                                                       * particles(n)%speed_y
4694                pos_z = pos_z + ( t(t_index) - t_old ) * dt_particle           &
4695                                                       * particles(n)%speed_z
4696!
4697!--             Obtain x/y grid indices for intermediate particle position from
4698!--             sorted index array
4699                i3 = x_ind(t_index)
4700                j3 = y_ind(t_index)
4701                k3 = z_ind(t_index)
4702!
4703!--             Check which wall is already reached
4704                IF ( .NOT. x_wall_reached )  x_wall_reached = reach_x(t_index) 
4705                IF ( .NOT. y_wall_reached )  y_wall_reached = reach_y(t_index)
4706                IF ( .NOT. z_wall_reached )  z_wall_reached = reach_z(t_index)
4707!
4708!--             Check if a particle needs to be reflected at any yz-wall. If
4709!--             necessary, carry out reflection. Please note, a security
4710!--             constant is required, as the particle position does not
4711!--             necessarily exactly match the wall location due to rounding
4712!--             errors.
4713                IF ( reach_x(t_index)                      .AND.               & 
4714                     ABS( pos_x - xwall ) < eps            .AND.               &
4715                     .NOT. BTEST(wall_flags_0(k3,j3,i3),0) .AND.               &
4716                     .NOT. reflect_x )  THEN
4717!
4718!
4719!--                Reflection in x-direction.
4720!--                Ensure correct reflection by MIN/MAX functions, depending on
4721!--                direction of particle transport.
4722!--                Due to rounding errors pos_x does not exactly match the wall
4723!--                location, leading to erroneous reflection.             
4724                   pos_x = MERGE( MIN( 2.0_wp * xwall - pos_x, xwall ),        &
4725                                  MAX( 2.0_wp * xwall - pos_x, xwall ),        &
4726                                  particles(n)%x > xwall )
4727!
4728!--                Change sign of particle speed                     
4729                   particles(n)%speed_x = - particles(n)%speed_x
4730!
4731!--                Also change sign of subgrid-scale particle speed
4732                   particles(n)%rvar1 = - particles(n)%rvar1
4733!
4734!--                Set flag that reflection along x is already done
4735                   reflect_x          = .TRUE.
4736!
4737!--                As the particle does not cross any further yz-wall during
4738!--                this timestep, set further x-indices to the current one.
4739                   x_ind(t_index:t_index_number) = i1
4740!
4741!--             If particle already reached the wall but was not reflected,
4742!--             set further x-indices to the new one.
4743                ELSEIF ( x_wall_reached .AND. .NOT. reflect_x )  THEN
4744                    x_ind(t_index:t_index_number) = i2
4745                ENDIF !particle reflection in x direction done
4746
4747!
4748!--             Check if a particle needs to be reflected at any xz-wall. If
4749!--             necessary, carry out reflection. Please note, a security
4750!--             constant is required, as the particle position does not
4751!--             necessarily exactly match the wall location due to rounding
4752!--             errors.
4753                IF ( reach_y(t_index)                      .AND.               & 
4754                     ABS( pos_y - ywall ) < eps            .AND.               &
4755                     .NOT. BTEST(wall_flags_0(k3,j3,i3),0) .AND.               &
4756                     .NOT. reflect_y )  THEN
4757!
4758!
4759!--                Reflection in y-direction.
4760!--                Ensure correct reflection by MIN/MAX functions, depending on
4761!--                direction of particle transport.
4762!--                Due to rounding errors pos_y does not exactly match the wall
4763!--                location, leading to erroneous reflection.             
4764                   pos_y = MERGE( MIN( 2.0_wp * ywall - pos_y, ywall ),        &
4765                                  MAX( 2.0_wp * ywall - pos_y, ywall ),        &
4766                                  particles(n)%y > ywall )
4767!
4768!--                Change sign of particle speed                     
4769                   particles(n)%speed_y = - particles(n)%speed_y
4770!
4771!--                Also change sign of subgrid-scale particle speed
4772                   particles(n)%rvar2 = - particles(n)%rvar2
4773!
4774!--                Set flag that reflection along y is already done
4775                   reflect_y          = .TRUE.
4776!
4777!--                As the particle does not cross any further xz-wall during
4778!--                this timestep, set further y-indices to the current one.
4779                   y_ind(t_index:t_index_number) = j1
4780!
4781!--             If particle already reached the wall but was not reflected,
4782!--             set further y-indices to the new one.
4783                ELSEIF ( y_wall_reached .AND. .NOT. reflect_y )  THEN
4784                    y_ind(t_index:t_index_number) = j2
4785                ENDIF !particle reflection in y direction done
4786
4787!
4788!--             Check if a particle needs to be reflected at any xy-wall. If
4789!--             necessary, carry out reflection. Please note, a security
4790!--             constant is required, as the particle position does not
4791!--             necessarily exactly match the wall location due to rounding
4792!--             errors.
4793                IF ( reach_z(t_index)                      .AND.               & 
4794                     ABS( pos_z - zwall ) < eps            .AND.               &
4795                     .NOT. BTEST(wall_flags_0(k3,j3,i3),0) .AND.               &
4796                     .NOT. reflect_z )  THEN
4797!
4798!
4799!--                Reflection in z-direction.
4800!--                Ensure correct reflection by MIN/MAX functions, depending on
4801!--                direction of particle transport.
4802!--                Due to rounding errors pos_z does not exactly match the wall
4803!--                location, leading to erroneous reflection.             
4804                   pos_z = MERGE( MIN( 2.0_wp * zwall - pos_z, zwall ),        &
4805                                  MAX( 2.0_wp * zwall - pos_z, zwall ),        &
4806                                  particles(n)%z > zwall )
4807!
4808!--                Change sign of particle speed                     
4809                   particles(n)%speed_z = - particles(n)%speed_z
4810!
4811!--                Also change sign of subgrid-scale particle speed
4812                   particles(n)%rvar3 = - particles(n)%rvar3
4813!
4814!--                Set flag that reflection along z is already done
4815                   reflect_z          = .TRUE.
4816!
4817!--                As the particle does not cross any further xy-wall during
4818!--                this timestep, set further z-indices to the current one.
4819                   z_ind(t_index:t_index_number) = k1
4820!
4821!--             If particle already reached the wall but was not reflected,
4822!--             set further z-indices to the new one.
4823                ELSEIF ( z_wall_reached .AND. .NOT. reflect_z )  THEN
4824                    z_ind(t_index:t_index_number) = k2
4825                ENDIF !particle reflection in z direction done               
4826
4827!
4828!--             Swap time
4829                t_old = t(t_index)
4830
4831             ENDDO
4832!
4833!--          If a particle was reflected, calculate final position from last
4834!--          intermediate position.
4835             IF ( reflect_x .OR. reflect_y .OR. reflect_z )  THEN
4836
4837                particles(n)%x = pos_x + ( 1.0_wp - t_old ) * dt_particle      &
4838                                                         * particles(n)%speed_x
4839                particles(n)%y = pos_y + ( 1.0_wp - t_old ) * dt_particle      &
4840                                                         * particles(n)%speed_y
4841                particles(n)%z = pos_z + ( 1.0_wp - t_old ) * dt_particle      &
4842                                                         * particles(n)%speed_z
4843
4844             ENDIF
4845
4846          ENDIF
4847
4848       ENDDO
4849
4850       CALL cpu_log( log_point_s(48), 'lpm_wall_reflect', 'stop' )
4851
4852       CASE DEFAULT
4853          CONTINUE
4854
4855    END SELECT
4856
4857 END SUBROUTINE lpm_boundary_conds 
4858
4859
4860!------------------------------------------------------------------------------!
4861! Description:
4862! ------------
4863!> Calculates change in droplet radius by condensation/evaporation, using
4864!> either an analytic formula or by numerically integrating the radius growth
4865!> equation including curvature and solution effects using Rosenbrocks method
4866!> (see Numerical recipes in FORTRAN, 2nd edition, p. 731).
4867!> The analytical formula and growth equation follow those given in
4868!> Rogers and Yau (A short course in cloud physics, 3rd edition, p. 102/103).
4869!------------------------------------------------------------------------------!
4870 SUBROUTINE lpm_droplet_condensation (i,j,k)
4871
4872    INTEGER(iwp), INTENT(IN) :: i              !<
4873    INTEGER(iwp), INTENT(IN) :: j              !<
4874    INTEGER(iwp), INTENT(IN) :: k              !<
4875    INTEGER(iwp) :: n                          !<
4876
4877    REAL(wp) ::  afactor                       !< curvature effects
4878    REAL(wp) ::  arg                           !<
4879    REAL(wp) ::  bfactor                       !< solute effects
4880    REAL(wp) ::  ddenom                        !<
4881    REAL(wp) ::  delta_r                       !<
4882    REAL(wp) ::  diameter                      !< diameter of cloud droplets
4883    REAL(wp) ::  diff_coeff                    !< diffusivity for water vapor
4884    REAL(wp) ::  drdt                          !<
4885    REAL(wp) ::  dt_ros                        !<
4886    REAL(wp) ::  dt_ros_sum                    !<
4887    REAL(wp) ::  d2rdtdr                       !<
4888    REAL(wp) ::  e_a                           !< current vapor pressure
4889    REAL(wp) ::  e_s                           !< current saturation vapor pressure
4890    REAL(wp) ::  error                         !< local truncation error in Rosenbrock
4891    REAL(wp) ::  k1                            !<
4892    REAL(wp) ::  k2                            !<
4893    REAL(wp) ::  r_err                         !< First order estimate of Rosenbrock radius
4894    REAL(wp) ::  r_ros                         !< Rosenbrock radius
4895    REAL(wp) ::  r_ros_ini                     !< initial Rosenbrock radius
4896    REAL(wp) ::  r0                            !< gas-kinetic lengthscale
4897    REAL(wp) ::  sigma                         !< surface tension of water
4898    REAL(wp) ::  thermal_conductivity          !< thermal conductivity for water
4899    REAL(wp) ::  t_int                         !< temperature
4900    REAL(wp) ::  w_s                           !< terminal velocity of droplets
4901    REAL(wp) ::  re_p                          !< particle Reynolds number
4902!
4903!-- Parameters for Rosenbrock method (see Verwer et al., 1999)
4904    REAL(wp), PARAMETER :: prec = 1.0E-3_wp     !< precision of Rosenbrock solution
4905    REAL(wp), PARAMETER :: q_increase = 1.5_wp  !< increase factor in timestep
4906    REAL(wp), PARAMETER :: q_decrease = 0.9_wp  !< decrease factor in timestep
4907    REAL(wp), PARAMETER :: gamma = 0.292893218814_wp !< = 1.0 - 1.0 / SQRT(2.0)
4908!
4909!-- Parameters for terminal velocity
4910    REAL(wp), PARAMETER ::  a_rog = 9.65_wp      !< parameter for fall velocity
4911    REAL(wp), PARAMETER ::  b_rog = 10.43_wp     !< parameter for fall velocity
4912    REAL(wp), PARAMETER ::  c_rog = 0.6_wp       !< parameter for fall velocity
4913    REAL(wp), PARAMETER ::  k_cap_rog = 4.0_wp   !< parameter for fall velocity
4914    REAL(wp), PARAMETER ::  k_low_rog = 12.0_wp  !< parameter for fall velocity
4915    REAL(wp), PARAMETER ::  d0_rog = 0.745_wp    !< separation diameter
4916
4917    REAL(wp), DIMENSION(number_of_particles) ::  ventilation_effect     !<
4918    REAL(wp), DIMENSION(number_of_particles) ::  new_r                  !<
4919
4920    CALL cpu_log( log_point_s(42), 'lpm_droplet_condens', 'start' )
4921
4922!
4923!-- Absolute temperature
4924    t_int = pt(k,j,i) * exner(k)
4925!
4926!-- Saturation vapor pressure (Eq. 10 in Bolton, 1980)
4927    e_s = magnus( t_int )
4928!
4929!-- Current vapor pressure
4930    e_a = q(k,j,i) * hyp(k) / ( q(k,j,i) + rd_d_rv )
4931!
4932!-- Thermal conductivity for water (from Rogers and Yau, Table 7.1)
4933    thermal_conductivity = 7.94048E-05_wp * t_int + 0.00227011_wp
4934!
4935!-- Moldecular diffusivity of water vapor in air (Hall und Pruppacher, 1976)
4936    diff_coeff           = 0.211E-4_wp * ( t_int / 273.15_wp )**1.94_wp * &
4937                           ( 101325.0_wp / hyp(k) )
4938!
4939!-- Lengthscale for gas-kinetic effects (from Mordy, 1959, p. 23):
4940    r0 = diff_coeff / 0.036_wp * SQRT( 2.0_wp * pi / ( r_v * t_int ) )
4941!
4942!-- Calculate effects of heat conductivity and diffusion of water vapor on the
4943!-- diffusional growth process (usually known as 1.0 / (F_k + F_d) )
4944    ddenom  = 1.0_wp / ( rho_l * r_v * t_int / ( e_s * diff_coeff ) +          &
4945                         ( l_v / ( r_v * t_int ) - 1.0_wp ) * rho_l *          &
4946                         l_v / ( thermal_conductivity * t_int )                &
4947                       )
4948    new_r = 0.0_wp
4949!
4950!-- Determine ventilation effect on evaporation of large drops
4951    DO  n = 1, number_of_particles
4952
4953       IF ( particles(n)%radius >= 4.0E-5_wp  .AND.  e_a / e_s < 1.0_wp )  THEN
4954!
4955!--       Terminal velocity is computed for vertical direction (Rogers et al.,
4956!--       1993, J. Appl. Meteorol.)
4957          diameter = particles(n)%radius * 2000.0_wp !diameter in mm
4958          IF ( diameter <= d0_rog )  THEN
4959             w_s = k_cap_rog * diameter * ( 1.0_wp - EXP( -k_low_rog * diameter ) )
4960          ELSE
4961             w_s = a_rog - b_rog * EXP( -c_rog * diameter )
4962          ENDIF
4963!
4964!--       Calculate droplet's Reynolds number
4965          re_p = 2.0_wp * particles(n)%radius * w_s / molecular_viscosity
4966!
4967!--       Ventilation coefficient (Rogers and Yau, 1989):
4968          IF ( re_p > 2.5_wp )  THEN
4969             ventilation_effect(n) = 0.78_wp + 0.28_wp * SQRT( re_p )
4970          ELSE
4971             ventilation_effect(n) = 1.0_wp + 0.09_wp * re_p
4972          ENDIF
4973       ELSE
4974!
4975!--       For small droplets or in supersaturated environments, the ventilation
4976!--       effect does not play a role
4977          ventilation_effect(n) = 1.0_wp
4978       ENDIF
4979    ENDDO
4980
4981    IF( .NOT. curvature_solution_effects ) then
4982!
4983!--    Use analytic model for diffusional growth including gas-kinetic
4984!--    effects (Mordy, 1959) but without the impact of aerosols.
4985       DO  n = 1, number_of_particles
4986          arg      = ( particles(n)%radius + r0 )**2 + 2.0_wp * dt_3d * ddenom * &
4987                                                       ventilation_effect(n) *   &
4988                                                       ( e_a / e_s - 1.0_wp )
4989          arg      = MAX( arg, ( 0.01E-6 + r0 )**2 )
4990          new_r(n) = SQRT( arg ) - r0
4991       ENDDO
4992
4993    ELSE
4994!
4995!--    Integrate the diffusional growth including gas-kinetic (Mordy, 1959),
4996!--    as well as curvature and solute effects (e.g., Köhler, 1936).
4997!
4998!--    Curvature effect (afactor) with surface tension (sigma) by Straka (2009)
4999       sigma = 0.0761_wp - 0.000155_wp * ( t_int - 273.15_wp )
5000!
5001!--    Solute effect (afactor)
5002       afactor = 2.0_wp * sigma / ( rho_l * r_v * t_int )
5003
5004       DO  n = 1, number_of_particles
5005!
5006!--       Solute effect (bfactor)
5007          bfactor = vanthoff * rho_s * particles(n)%aux1**3 *                    &
5008                    molecular_weight_of_water / ( rho_l * molecular_weight_of_solute )
5009
5010          dt_ros     = particles(n)%aux2  ! use previously stored Rosenbrock timestep
5011          dt_ros_sum = 0.0_wp
5012
5013          r_ros     = particles(n)%radius  ! initialize Rosenbrock particle radius
5014          r_ros_ini = r_ros
5015!
5016!--       Integrate growth equation using a 2nd-order Rosenbrock method
5017!--       (see Verwer et al., 1999, Eq. (3.2)). The Rosenbrock method adjusts
5018!--       its with internal timestep to minimize the local truncation error.
5019          DO WHILE ( dt_ros_sum < dt_3d )
5020
5021             dt_ros = MIN( dt_ros, dt_3d - dt_ros_sum )
5022
5023             DO
5024
5025                drdt = ddenom * ventilation_effect(n) * ( e_a / e_s - 1.0_wp - &
5026                                                          afactor / r_ros +    &
5027                                                          bfactor / r_ros**3   &
5028                                                        ) / ( r_ros + r0 )
5029
5030                d2rdtdr = -ddenom * ventilation_effect(n) * (                  &
5031                                            (e_a / e_s - 1.0_wp ) * r_ros**4 - &
5032                                            afactor * r0 * r_ros**2 -          &
5033                                            2.0_wp * afactor * r_ros**3 +      &
5034                                            3.0_wp * bfactor * r0 +            &
5035                                            4.0_wp * bfactor * r_ros           &
5036                                                            )                  &
5037                          / ( r_ros**4 * ( r_ros + r0 )**2 )
5038
5039                k1    = drdt / ( 1.0_wp - gamma * dt_ros * d2rdtdr )
5040
5041                r_ros = MAX(r_ros_ini + k1 * dt_ros, particles(n)%aux1)
5042                r_err = r_ros
5043
5044                drdt  = ddenom * ventilation_effect(n) * ( e_a / e_s - 1.0_wp - &
5045                                                           afactor / r_ros +    &
5046                                                           bfactor / r_ros**3   &
5047                                                         ) / ( r_ros + r0 )
5048
5049                k2 = ( drdt - dt_ros * 2.0 * gamma * d2rdtdr * k1 ) / &
5050                     ( 1.0_wp - dt_ros * gamma * d2rdtdr )
5051
5052                r_ros = MAX(r_ros_ini + dt_ros * ( 1.5_wp * k1 + 0.5_wp * k2), particles(n)%aux1)
5053   !
5054   !--          Check error of the solution, and reduce dt_ros if necessary.
5055                error = ABS(r_err - r_ros) / r_ros
5056                IF ( error .GT. prec )  THEN
5057                   dt_ros = SQRT( q_decrease * prec / error ) * dt_ros
5058                   r_ros  = r_ros_ini
5059                ELSE
5060                   dt_ros_sum = dt_ros_sum + dt_ros
5061                   dt_ros     = q_increase * dt_ros
5062                   r_ros_ini  = r_ros
5063                   EXIT
5064                ENDIF
5065
5066             END DO
5067
5068          END DO !Rosenbrock loop
5069!
5070!--       Store new particle radius
5071          new_r(n) = r_ros
5072!
5073!--       Store internal time step value for next PALM step
5074          particles(n)%aux2 = dt_ros
5075
5076       ENDDO !Particle loop
5077
5078    ENDIF
5079
5080    DO  n = 1, number_of_particles
5081!
5082!--    Sum up the change in liquid water for the respective grid
5083!--    box for the computation of the release/depletion of water vapor
5084!--    and heat.
5085       ql_c(k,j,i) = ql_c(k,j,i) + particles(n)%weight_factor *          &
5086                                   rho_l * 1.33333333_wp * pi *                &
5087                                   ( new_r(n)**3 - particles(n)%radius**3 ) /  &
5088                                   ( rho_surface * dx * dy * dzw(k) )
5089!
5090!--    Check if the increase in liqid water is not too big. If this is the case,
5091!--    the model timestep might be too long.
5092       IF ( ql_c(k,j,i) > 100.0_wp )  THEN
5093          WRITE( message_string, * ) 'k=',k,' j=',j,' i=',i,                &
5094                       ' ql_c=',ql_c(k,j,i), '&part(',n,')%wf=',            &
5095                       particles(n)%weight_factor,' delta_r=',delta_r
5096          CALL message( 'lpm_droplet_condensation', 'PA0143', 2, 2, -1, 6, 1 )
5097       ENDIF
5098!
5099!--    Check if the change in the droplet radius is not too big. If this is the
5100!--    case, the model timestep might be too long.
5101       delta_r = new_r(n) - particles(n)%radius
5102       IF ( delta_r < 0.0_wp  .AND. new_r(n) < 0.0_wp )  THEN
5103          WRITE( message_string, * ) '#1 k=',k,' j=',j,' i=',i,             &
5104                       ' e_s=',e_s, ' e_a=',e_a,' t_int=',t_int,               &
5105                       '&delta_r=',delta_r,                                    &
5106                       ' particle_radius=',particles(n)%radius
5107          CALL message( 'lpm_droplet_condensation', 'PA0144', 2, 2, -1, 6, 1 )
5108       ENDIF
5109!
5110!--    Sum up the total volume of liquid water (needed below for
5111!--    re-calculating the weighting factors)
5112       ql_v(k,j,i) = ql_v(k,j,i) + particles(n)%weight_factor * new_r(n)**3
5113!
5114!--    Determine radius class of the particle needed for collision
5115       IF ( use_kernel_tables )  THEN
5116          particles(n)%class = ( LOG( new_r(n) ) - rclass_lbound ) /           &
5117                               ( rclass_ubound - rclass_lbound ) *             &
5118                               radius_classes
5119          particles(n)%class = MIN( particles(n)%class, radius_classes )
5120          particles(n)%class = MAX( particles(n)%class, 1 )
5121       ENDIF
5122!
5123!--    Store new radius to particle features
5124       particles(n)%radius = new_r(n)
5125
5126    ENDDO
5127
5128    CALL cpu_log( log_point_s(42), 'lpm_droplet_condens', 'stop' )
5129
5130
5131 END SUBROUTINE lpm_droplet_condensation
5132
5133
5134!------------------------------------------------------------------------------!
5135! Description:
5136! ------------
5137!> Release of latent heat and change of mixing ratio due to condensation /
5138!> evaporation of droplets.
5139!------------------------------------------------------------------------------!
5140 SUBROUTINE lpm_interaction_droplets_ptq
5141
5142    INTEGER(iwp) ::  i    !< running index x direction
5143    INTEGER(iwp) ::  j    !< running index y direction
5144    INTEGER(iwp) ::  k    !< running index z direction
5145
5146    REAL(wp) ::  flag     !< flag to mask topography grid points
5147
5148    DO  i = nxl, nxr
5149       DO  j = nys, nyn
5150          DO  k = nzb+1, nzt
5151!
5152!--          Predetermine flag to mask topography
5153             flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
5154
5155             q_p(k,j,i)  = q_p(k,j,i)  - ql_c(k,j,i) * flag
5156             pt_p(k,j,i) = pt_p(k,j,i) + lv_d_cp * ql_c(k,j,i) * d_exner(k) &
5157                                                     * flag
5158          ENDDO
5159       ENDDO
5160    ENDDO
5161
5162 END SUBROUTINE lpm_interaction_droplets_ptq
5163
5164
5165!------------------------------------------------------------------------------!
5166! Description:
5167! ------------
5168!> Release of latent heat and change of mixing ratio due to condensation /
5169!> evaporation of droplets. Call for grid point i,j
5170!------------------------------------------------------------------------------!
5171 SUBROUTINE lpm_interaction_droplets_ptq_ij( i, j )
5172
5173    INTEGER(iwp) ::  i    !< running index x direction
5174    INTEGER(iwp) ::  j    !< running index y direction
5175    INTEGER(iwp) ::  k    !< running index z direction
5176
5177    REAL(wp) ::  flag     !< flag to mask topography grid points
5178
5179
5180    DO  k = nzb+1, nzt
5181!
5182!--    Predetermine flag to mask topography
5183       flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
5184
5185       q_p(k,j,i)  = q_p(k,j,i)  - ql_c(k,j,i) * flag
5186       pt_p(k,j,i) = pt_p(k,j,i) + lv_d_cp * ql_c(k,j,i) * d_exner(k) * flag
5187    ENDDO
5188
5189 END SUBROUTINE lpm_interaction_droplets_ptq_ij
5190
5191
5192!------------------------------------------------------------------------------!
5193! Description:
5194! ------------
5195!> Calculate the liquid water content for each grid box.
5196!------------------------------------------------------------------------------!
5197 SUBROUTINE lpm_calc_liquid_water_content
5198
5199
5200    INTEGER(iwp) ::  i   !<
5201    INTEGER(iwp) ::  j   !<
5202    INTEGER(iwp) ::  k   !<
5203    INTEGER(iwp) ::  n   !<
5204
5205    CALL cpu_log( log_point_s(45), 'lpm_calc_ql', 'start' )
5206
5207!
5208!-- Set water content initially to zero
5209    ql = 0.0_wp;  ql_v = 0.0_wp;  ql_vp = 0.0_wp
5210
5211!
5212!-- Calculate for each grid box
5213    DO  i = nxl, nxr
5214       DO  j = nys, nyn
5215          DO  k = nzb+1, nzt
5216             number_of_particles = prt_count(k,j,i)
5217             IF ( number_of_particles <= 0 )  CYCLE
5218             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
5219!
5220!--          Calculate the total volume in the boxes (ql_v, weighting factor
5221!--          has to beincluded)
5222             DO  n = 1, prt_count(k,j,i)
5223                ql_v(k,j,i)  = ql_v(k,j,i)  + particles(n)%weight_factor *     &
5224                                              particles(n)%radius**3
5225             ENDDO
5226!
5227!--          Calculate the liquid water content
5228             IF ( ql_v(k,j,i) /= 0.0_wp )  THEN
5229                ql(k,j,i) = ql(k,j,i) + rho_l * 1.33333333_wp * pi *           &
5230                                        ql_v(k,j,i) /                          &
5231                                        ( rho_surface * dx * dy * dzw(k) )
5232                IF ( ql(k,j,i) < 0.0_wp )  THEN
5233                   WRITE( message_string, * )  'LWC out of range: ' , &
5234                                               ql(k,j,i),i,j,k
5235                   CALL message( 'lpm_calc_liquid_water_content', '', 2, 2,    &
5236                                 -1, 6, 1 )
5237                ENDIF
5238             ELSE
5239                ql(k,j,i) = 0.0_wp
5240             ENDIF
5241          ENDDO
5242       ENDDO
5243    ENDDO
5244
5245    CALL cpu_log( log_point_s(45), 'lpm_calc_ql', 'stop' )
5246
5247 END SUBROUTINE lpm_calc_liquid_water_content
5248
5249
5250!------------------------------------------------------------------------------!
5251! Description:
5252! ------------
5253!> Calculates change in droplet radius by collision. Droplet collision is
5254!> calculated for each grid box seperately. Collision is parameterized by
5255!> using collision kernels. Two different kernels are available:
5256!> Hall kernel: Kernel from Hall (1980, J. Atmos. Sci., 2486-2507), which
5257!>              considers collision due to pure gravitational effects.
5258!> Wang kernel: Beside gravitational effects (treated with the Hall-kernel) also
5259!>              the effects of turbulence on the collision are considered using
5260!>              parameterizations of Ayala et al. (2008, New J. Phys., 10,
5261!>              075015) and Wang and Grabowski (2009, Atmos. Sci. Lett., 10,
5262!>              1-8). This kernel includes three possible effects of turbulence:
5263!>              the modification of the relative velocity between the droplets,
5264!>              the effect of preferential concentration, and the enhancement of
5265!>              collision efficiencies.
5266!------------------------------------------------------------------------------!
5267 SUBROUTINE lpm_droplet_collision (i,j,k)
5268
5269    INTEGER(iwp), INTENT(IN) ::  i        !<
5270    INTEGER(iwp), INTENT(IN) ::  j        !<
5271    INTEGER(iwp), INTENT(IN) ::  k        !<
5272
5273    INTEGER(iwp) ::  eclass   !<
5274    INTEGER(iwp) ::  n        !<
5275    INTEGER(iwp) ::  m        !<
5276    INTEGER(iwp) ::  rclass_l !<
5277    INTEGER(iwp) ::  rclass_s !<
5278
5279    REAL(wp) ::  collection_probability  !< probability for collection
5280    REAL(wp) ::  ddV                     !< inverse grid box volume
5281    REAL(wp) ::  epsilon_collision       !< dissipation rate
5282    REAL(wp) ::  factor_volume_to_mass   !< 4.0 / 3.0 * pi * rho_l
5283    REAL(wp) ::  xm                      !< droplet mass of super-droplet m
5284    REAL(wp) ::  xn                      !< droplet mass of super-droplet n
5285    REAL(wp) ::  xsm                     !< aerosol mass of super-droplet m
5286    REAL(wp) ::  xsn                     !< aerosol mass of super-droplet n
5287
5288    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight    !< weighting factor
5289    REAL(wp), DIMENSION(:), ALLOCATABLE ::  mass      !< total mass of super droplet
5290    REAL(wp), DIMENSION(:), ALLOCATABLE ::  aero_mass !< total aerosol mass of super droplet
5291
5292    CALL cpu_log( log_point_s(43), 'lpm_droplet_coll', 'start' )
5293
5294    number_of_particles   = prt_count(k,j,i)
5295    factor_volume_to_mass = 4.0_wp / 3.0_wp * pi * rho_l
5296    ddV                   = 1.0_wp / ( dx * dy * dzw(k) )
5297!
5298!-- Collision requires at least one super droplet inside the box
5299    IF ( number_of_particles > 0 )  THEN
5300
5301       IF ( use_kernel_tables )  THEN
5302!
5303!--       Fast method with pre-calculated collection kernels for
5304!--       discrete radius- and dissipation-classes.
5305          IF ( wang_kernel )  THEN
5306             eclass = INT( diss(k,j,i) * 1.0E4_wp / 600.0_wp * &
5307                           dissipation_classes ) + 1
5308             epsilon_collision = diss(k,j,i)
5309          ELSE
5310             epsilon_collision = 0.0_wp
5311          ENDIF
5312
5313          IF ( hall_kernel  .OR.  epsilon_collision * 1.0E4_wp < 0.001_wp )  THEN
5314             eclass = 0   ! Hall kernel is used
5315          ELSE
5316             eclass = MIN( dissipation_classes, eclass )
5317          ENDIF
5318
5319       ELSE
5320!
5321!--       Collection kernels are re-calculated for every new
5322!--       grid box. First, allocate memory for kernel table.
5323!--       Third dimension is 1, because table is re-calculated for
5324!--       every new dissipation value.
5325          ALLOCATE( ckernel(1:number_of_particles,1:number_of_particles,1:1) )
5326!
5327!--       Now calculate collection kernel for this box. Note that
5328!--       the kernel is based on the previous time step
5329          CALL recalculate_kernel( i, j, k )
5330
5331       ENDIF
5332!
5333!--    Temporary fields for total mass of super-droplet, aerosol mass, and
5334!--    weighting factor are allocated.
5335       ALLOCATE(mass(1:number_of_particles), weight(1:number_of_particles))
5336       IF ( curvature_solution_effects )  ALLOCATE(aero_mass(1:number_of_particles))
5337
5338       mass(1:number_of_particles)   = particles(1:number_of_particles)%weight_factor * &
5339                                       particles(1:number_of_particles)%radius**3     * &
5340                                       factor_volume_to_mass
5341
5342       weight(1:number_of_particles) = particles(1:number_of_particles)%weight_factor
5343
5344       IF ( curvature_solution_effects )  THEN
5345          aero_mass(1:number_of_particles) = particles(1:number_of_particles)%weight_factor * &
5346                                             particles(1:number_of_particles)%aux1**3       * &
5347                                             4.0_wp / 3.0_wp * pi * rho_s
5348       ENDIF
5349!
5350!--    Calculate collision/coalescence
5351       DO  n = 1, number_of_particles
5352
5353          DO  m = n, number_of_particles
5354!
5355!--          For collisions, the weighting factor of at least one super-droplet
5356!--          needs to be larger or equal to one.
5357             IF ( MIN( weight(n), weight(m) ) .LT. 1.0_wp )  CYCLE
5358!
5359!--          Get mass of individual droplets (aerosols)
5360             xn = mass(n) / weight(n)
5361             xm = mass(m) / weight(m)
5362             IF ( curvature_solution_effects )  THEN
5363                xsn = aero_mass(n) / weight(n)
5364                xsm = aero_mass(m) / weight(m)
5365             ENDIF
5366!
5367!--          Probability that the necessary collisions take place
5368             IF ( use_kernel_tables )  THEN
5369                rclass_l = particles(n)%class
5370                rclass_s = particles(m)%class
5371
5372                collection_probability  = MAX( weight(n), weight(m) ) *     &
5373                                          ckernel(rclass_l,rclass_s,eclass) * ddV * dt_3d
5374             ELSE
5375                collection_probability  = MAX( weight(n), weight(m) ) *     &
5376                                          ckernel(n,m,1) * ddV * dt_3d
5377             ENDIF
5378!
5379!--          Calculate the number of collections and consider multiple collections.
5380!--          (Accordingly, p_crit will be 0.0, 1.0, 2.0, ...)
5381             IF ( collection_probability - FLOOR(collection_probability)    &
5382                  .GT. random_function( iran_part ) )  THEN
5383                collection_probability = FLOOR(collection_probability) + 1.0_wp
5384             ELSE
5385                collection_probability = FLOOR(collection_probability)
5386             ENDIF
5387
5388             IF ( collection_probability .GT. 0.0_wp )  THEN
5389!
5390!--             Super-droplet n collects droplets of super-droplet m
5391                IF ( weight(n) .LT. weight(m) )  THEN
5392
5393                   mass(n)   = mass(n)   + weight(n) * xm * collection_probability
5394                   weight(m) = weight(m) - weight(n)      * collection_probability
5395                   mass(m)   = mass(m)   - weight(n) * xm * collection_probability
5396                   IF ( curvature_solution_effects )  THEN
5397                      aero_mass(n) = aero_mass(n) + weight(n) * xsm * collection_probability
5398                      aero_mass(m) = aero_mass(m) - weight(n) * xsm * collection_probability
5399                   ENDIF
5400
5401                ELSEIF ( weight(m) .LT. weight(n) )  THEN
5402
5403                   mass(m)   = mass(m)   + weight(m) * xn * collection_probability
5404                   weight(n) = weight(n) - weight(m)      * collection_probability
5405                   mass(n)   = mass(n)   - weight(m) * xn * collection_probability
5406                   IF ( curvature_solution_effects )  THEN
5407                      aero_mass(m) = aero_mass(m) + weight(m) * xsn * collection_probability
5408                      aero_mass(n) = aero_mass(n) - weight(m) * xsn * collection_probability
5409                   ENDIF
5410
5411                ELSE
5412!
5413!--                Collisions of particles of the same weighting factor.
5414!--                Particle n collects 1/2 weight(n) droplets of particle m,
5415!--                particle m collects 1/2 weight(m) droplets of particle n.
5416!--                The total mass mass changes accordingly.
5417!--                If n = m, the first half of the droplets coalesces with the
5418!--                second half of the droplets; mass is unchanged because
5419!--                xm = xn for n = m.
5420!--
5421!--                Note: For m = n this equation is an approximation only
5422!--                valid for weight >> 1 (which is usually the case). The
5423!--                approximation is weight(n)-1 = weight(n).
5424                   mass(n)   = mass(n)   + 0.5_wp * weight(n) * ( xm - xn )
5425                   mass(m)   = mass(m)   + 0.5_wp * weight(m) * ( xn - xm )
5426                   IF ( curvature_solution_effects )  THEN
5427                      aero_mass(n) = aero_mass(n) + 0.5_wp * weight(n) * ( xsm - xsn )
5428                      aero_mass(m) = aero_mass(m) + 0.5_wp * weight(m) * ( xsn - xsm )
5429                   ENDIF
5430                   weight(n) = weight(n) - 0.5_wp * weight(m)
5431                   weight(m) = weight(n)
5432
5433                ENDIF
5434
5435             ENDIF
5436
5437          ENDDO
5438
5439          ql_vp(k,j,i) = ql_vp(k,j,i) + mass(n) / factor_volume_to_mass
5440
5441       ENDDO
5442
5443       IF ( ANY(weight < 0.0_wp) )  THEN
5444             WRITE( message_string, * ) 'negative weighting factor'
5445             CALL message( 'lpm_droplet_collision', 'PA0028',      &
5446                            2, 2, -1, 6, 1 )
5447       ENDIF
5448
5449       particles(1:number_of_particles)%radius = ( mass(1:number_of_particles) /   &
5450                                                   ( weight(1:number_of_particles) &
5451                                                     * factor_volume_to_mass       &
5452                                                   )                               &
5453                                                 )**0.33333333333333_wp
5454
5455       IF ( curvature_solution_effects )  THEN
5456          particles(1:number_of_particles)%aux1 = ( aero_mass(1:number_of_particles) / &
5457                                                    ( weight(1:number_of_particles)    &
5458                                                      * 4.0_wp / 3.0_wp * pi * rho_s   &
5459                                                    )                                  &
5460                                                  )**0.33333333333333_wp
5461       ENDIF
5462
5463       particles(1:number_of_particles)%weight_factor = weight(1:number_of_particles)
5464
5465       DEALLOCATE( weight, mass )
5466       IF ( curvature_solution_effects )  DEALLOCATE( aero_mass )
5467       IF ( .NOT. use_kernel_tables )  DEALLOCATE( ckernel )
5468
5469!
5470!--    Check if LWC is conserved during collision process
5471       IF ( ql_v(k,j,i) /= 0.0_wp )  THEN
5472          IF ( ql_vp(k,j,i) / ql_v(k,j,i) >= 1.0001_wp  .OR.                      &
5473               ql_vp(k,j,i) / ql_v(k,j,i) <= 0.9999_wp )  THEN
5474             WRITE( message_string, * ) ' LWC is not conserved during',           &
5475                                        ' collision! ',                           &
5476                                        ' LWC after condensation: ', ql_v(k,j,i), &
5477                                        ' LWC after collision: ', ql_vp(k,j,i)
5478             CALL message( 'lpm_droplet_collision', 'PA0040', 2, 2, -1, 6, 1 )
5479          ENDIF
5480       ENDIF
5481
5482    ENDIF
5483
5484    CALL cpu_log( log_point_s(43), 'lpm_droplet_coll', 'stop' )
5485
5486 END SUBROUTINE lpm_droplet_collision
5487 
5488!------------------------------------------------------------------------------!
5489! Description:
5490! ------------
5491!> Initialization of the collision efficiency matrix with fixed radius and
5492!> dissipation classes, calculated at simulation start only.
5493!------------------------------------------------------------------------------!
5494 SUBROUTINE lpm_init_kernels
5495
5496    INTEGER(iwp) ::  i !<
5497    INTEGER(iwp) ::  j !<
5498    INTEGER(iwp) ::  k !<
5499   
5500!
5501!-- Calculate collision efficiencies for fixed radius- and dissipation
5502!-- classes
5503    IF ( collision_kernel(6:9) == 'fast' )  THEN
5504
5505       ALLOCATE( ckernel(1:radius_classes,1:radius_classes,                 &
5506                 0:dissipation_classes), epsclass(1:dissipation_classes),   &
5507                 radclass(1:radius_classes) )
5508
5509!
5510!--    Calculate the radius class bounds with logarithmic distances
5511!--    in the interval [1.0E-6, 1000.0E-6] m
5512       rclass_lbound = LOG( 1.0E-6_wp )
5513       rclass_ubound = LOG( 1000.0E-6_wp )
5514       radclass(1)   = EXP( rclass_lbound )
5515       DO  i = 2, radius_classes
5516          radclass(i) = EXP( rclass_lbound +                                &
5517                             ( rclass_ubound - rclass_lbound ) *            &
5518                             ( i - 1.0_wp ) / ( radius_classes - 1.0_wp ) )
5519       ENDDO
5520
5521!
5522!--    Set the class bounds for dissipation in interval [0.0, 600.0] cm**2/s**3
5523       DO  i = 1, dissipation_classes
5524          epsclass(i) = 0.06_wp * REAL( i, KIND=wp ) / dissipation_classes
5525       ENDDO
5526!
5527!--    Calculate collision efficiencies of the Wang/ayala kernel
5528       ALLOCATE( ec(1:radius_classes,1:radius_classes),  &
5529                 ecf(1:radius_classes,1:radius_classes), &
5530                 gck(1:radius_classes,1:radius_classes), &
5531                 winf(1:radius_classes) )
5532
5533       DO  k = 1, dissipation_classes
5534
5535          epsilon_collision = epsclass(k)
5536          urms    = 2.02_wp * ( epsilon_collision / 0.04_wp )**( 1.0_wp / 3.0_wp )
5537
5538          CALL turbsd
5539          CALL turb_enhance_eff
5540          CALL effic
5541
5542          DO  j = 1, radius_classes
5543             DO  i = 1, radius_classes
5544                ckernel(i,j,k) = ec(i,j) * gck(i,j) * ecf(i,j)
5545             ENDDO
5546          ENDDO
5547
5548       ENDDO
5549
5550!
5551!--    Calculate collision efficiencies of the Hall kernel
5552       ALLOCATE( hkernel(1:radius_classes,1:radius_classes), &
5553                 hwratio(1:radius_classes,1:radius_classes) )
5554
5555       CALL fallg
5556       CALL effic
5557
5558       DO  j = 1, radius_classes
5559          DO  i =  1, radius_classes
5560             hkernel(i,j) = pi * ( radclass(j) + radclass(i) )**2 &
5561                               * ec(i,j) * ABS( winf(j) - winf(i) )
5562             ckernel(i,j,0) = hkernel(i,j)  ! hall kernel stored on index 0
5563           ENDDO
5564       ENDDO
5565
5566!
5567!--    Test output of efficiencies
5568       IF ( j == -1 )  THEN
5569          PRINT*, '*** Hall kernel'
5570          WRITE ( *,'(5X,20(F4.0,1X))' ) ( radclass(i)*1.0E6_wp, &
5571                                           i = 1,radius_classes )
5572          DO  j = 1, radius_classes
5573             WRITE ( *,'(F4.0,1X,20(F8.4,1X))' ) radclass(j),  &
5574                                       ( hkernel(i,j), i = 1,radius_classes )
5575          ENDDO
5576
5577          DO  k = 1, dissipation_classes
5578             DO  i = 1, radius_classes
5579                DO  j = 1, radius_classes
5580                   IF ( hkernel(i,j) == 0.0_wp )  THEN
5581                      hwratio(i,j) = 9999999.9_wp
5582                   ELSE
5583                      hwratio(i,j) = ckernel(i,j,k) / hkernel(i,j)
5584                   ENDIF
5585                ENDDO
5586             ENDDO
5587
5588             PRINT*, '*** epsilon = ', epsclass(k)
5589             WRITE ( *,'(5X,20(F4.0,1X))' ) ( radclass(i) * 1.0E6_wp, &
5590                                              i = 1,radius_classes )
5591             DO  j = 1, radius_classes
5592                WRITE ( *,'(F4.0,1X,20(F8.4,1X))' ) radclass(j) * 1.0E6_wp, &
5593                                       ( hwratio(i,j), i = 1,radius_classes )
5594             ENDDO
5595          ENDDO
5596       ENDIF
5597
5598       DEALLOCATE( ec, ecf, epsclass, gck, hkernel, winf )
5599
5600    ENDIF
5601
5602 END SUBROUTINE lpm_init_kernels
5603 
5604!------------------------------------------------------------------------------!
5605! Description:
5606! ------------
5607!> Calculation of collision kernels during each timestep and for each grid box
5608!------------------------------------------------------------------------------!
5609 SUBROUTINE recalculate_kernel( i1, j1, k1 )
5610
5611
5612    INTEGER(iwp) ::  i      !<
5613    INTEGER(iwp) ::  i1     !<
5614    INTEGER(iwp) ::  j      !<
5615    INTEGER(iwp) ::  j1     !<
5616    INTEGER(iwp) ::  k1     !<
5617
5618
5619    number_of_particles = prt_count(k1,j1,i1)
5620    radius_classes      = number_of_particles   ! necessary to use the same
5621                                                ! subroutines as for
5622                                                ! precalculated kernels
5623
5624    ALLOCATE( ec(1:number_of_particles,1:number_of_particles), &
5625              radclass(1:number_of_particles), winf(1:number_of_particles) )
5626
5627!
5628!-- Store particle radii on the radclass array
5629    radclass(1:number_of_particles) = particles(1:number_of_particles)%radius
5630
5631    IF ( wang_kernel )  THEN
5632       epsilon_collision = diss(k1,j1,i1)   ! dissipation rate in m**2/s**3
5633    ELSE
5634       epsilon_collision = 0.0_wp
5635    ENDIF
5636    urms    = 2.02_wp * ( epsilon_collision / 0.04_wp )**( 0.33333333333_wp )
5637
5638    IF ( wang_kernel  .AND.  epsilon_collision > 1.0E-7_wp )  THEN
5639!
5640!--    Call routines to calculate efficiencies for the Wang kernel
5641       ALLOCATE( gck(1:number_of_particles,1:number_of_particles), &
5642                 ecf(1:number_of_particles,1:number_of_particles) )
5643
5644       CALL turbsd
5645       CALL turb_enhance_eff
5646       CALL effic
5647
5648       DO  j = 1, number_of_particles
5649          DO  i =  1, number_of_particles
5650             ckernel(1+i-1,1+j-1,1) = ec(i,j) * gck(i,j) * ecf(i,j)
5651          ENDDO
5652       ENDDO
5653
5654       DEALLOCATE( gck, ecf )
5655    ELSE
5656!
5657!--    Call routines to calculate efficiencies for the Hall kernel
5658       CALL fallg
5659       CALL effic
5660
5661       DO  j = 1, number_of_particles
5662          DO  i =  1, number_of_particles
5663             ckernel(i,j,1) = pi * ( radclass(j) + radclass(i) )**2         &
5664                                 * ec(i,j) * ABS( winf(j) - winf(i) )
5665          ENDDO
5666       ENDDO
5667    ENDIF
5668
5669    DEALLOCATE( ec, radclass, winf )
5670
5671 END SUBROUTINE recalculate_kernel
5672
5673!------------------------------------------------------------------------------!
5674! Description:
5675! ------------
5676!> Calculation of effects of turbulence on the geometric collision kernel
5677!> (by including the droplets' average radial relative velocities and their
5678!> radial distribution function) following the analytic model by Aayala et al.
5679!> (2008, New J. Phys.). For details check the second part 2 of the publication,
5680!> page 37ff.
5681!>
5682!> Input parameters, which need to be replaced by PALM parameters:
5683!>    water density, air density
5684!------------------------------------------------------------------------------!
5685 SUBROUTINE turbsd
5686
5687    INTEGER(iwp) ::  i     !<
5688    INTEGER(iwp) ::  j     !<
5689
5690    REAL(wp) ::  ao        !<
5691    REAL(wp) ::  ao_gr     !<
5692    REAL(wp) ::  bbb       !<
5693    REAL(wp) ::  be        !<
5694    REAL(wp) ::  b1        !<
5695    REAL(wp) ::  b2        !<
5696    REAL(wp) ::  ccc       !<
5697    REAL(wp) ::  c1        !<
5698    REAL(wp) ::  c1_gr     !<
5699    REAL(wp) ::  c2        !<
5700    REAL(wp) ::  d1        !<
5701    REAL(wp) ::  d2        !<
5702    REAL(wp) ::  eta       !<
5703    REAL(wp) ::  e1        !<
5704    REAL(wp) ::  e2        !<
5705    REAL(wp) ::  fao_gr    !<
5706    REAL(wp) ::  fr        !<
5707    REAL(wp) ::  grfin     !<
5708    REAL(wp) ::  lambda    !<
5709    REAL(wp) ::  lambda_re !<
5710    REAL(wp) ::  lf        !<
5711    REAL(wp) ::  rc        !<
5712    REAL(wp) ::  rrp       !<
5713    REAL(wp) ::  sst       !<
5714    REAL(wp) ::  tauk      !<
5715    REAL(wp) ::  tl        !<
5716    REAL(wp) ::  t2        !<
5717    REAL(wp) ::  tt        !<
5718    REAL(wp) ::  t1        !<
5719    REAL(wp) ::  vk        !<
5720    REAL(wp) ::  vrms1xy   !<
5721    REAL(wp) ::  vrms2xy   !<
5722    REAL(wp) ::  v1        !<
5723    REAL(wp) ::  v1v2xy    !<
5724    REAL(wp) ::  v1xysq    !<
5725    REAL(wp) ::  v2        !<
5726    REAL(wp) ::  v2xysq    !<
5727    REAL(wp) ::  wrfin     !<
5728    REAL(wp) ::  wrgrav2   !<
5729    REAL(wp) ::  wrtur2xy  !<
5730    REAL(wp) ::  xx        !<
5731    REAL(wp) ::  yy        !<
5732    REAL(wp) ::  z         !<
5733
5734    REAL(wp), DIMENSION(1:radius_classes) ::  st  !< Stokes number
5735    REAL(wp), DIMENSION(1:radius_classes) ::  tau !< inertial time scale
5736
5737    lambda    = urms * SQRT( 15.0_wp * molecular_viscosity / epsilon_collision )
5738    lambda_re = urms**2 * SQRT( 15.0_wp / epsilon_collision / molecular_viscosity )
5739    tl        = urms**2 / epsilon_collision
5740    lf        = 0.5_wp * urms**3 / epsilon_collision
5741    tauk      = SQRT( molecular_viscosity / epsilon_collision )
5742    eta       = ( molecular_viscosity**3 / epsilon_collision )**0.25_wp
5743    vk        = eta / tauk
5744
5745    ao = ( 11.0_wp + 7.0_wp * lambda_re ) / ( 205.0_wp + lambda_re )
5746    tt = SQRT( 2.0_wp * lambda_re / ( SQRT( 15.0_wp ) * ao ) ) * tauk
5747
5748!
5749!-- Get terminal velocity of droplets
5750    CALL fallg
5751
5752    DO  i = 1, radius_classes
5753       tau(i) = winf(i) / g    ! inertial time scale
5754       st(i)  = tau(i) / tauk  ! Stokes number
5755    ENDDO
5756
5757!
5758!-- Calculate average radial relative velocity at contact (wrfin)
5759    z   = tt / tl
5760    be  = SQRT( 2.0_wp ) * lambda / lf
5761    bbb = SQRT( 1.0_wp - 2.0_wp * be**2 )
5762    d1  = ( 1.0_wp + bbb ) / ( 2.0_wp * bbb )
5763    e1  = lf * ( 1.0_wp + bbb ) * 0.5_wp
5764    d2  = ( 1.0_wp - bbb ) * 0.5_wp / bbb
5765    e2  = lf * ( 1.0_wp - bbb ) * 0.5_wp
5766    ccc = SQRT( 1.0_wp - 2.0_wp * z**2 )
5767    b1  = ( 1.0_wp + ccc ) * 0.5_wp / ccc
5768    c1  = tl * ( 1.0_wp + ccc ) * 0.5_wp
5769    b2  = ( 1.0_wp - ccc ) * 0.5_wp / ccc
5770    c2  = tl * ( 1.0_wp - ccc ) * 0.5_wp
5771
5772    DO  i = 1, radius_classes
5773
5774       v1 = winf(i)
5775       t1 = tau(i)
5776
5777       DO  j = 1, i
5778          rrp = radclass(i) + radclass(j)
5779          v2  = winf(j)
5780          t2  = tau(j)
5781
5782          v1xysq  = b1 * d1 * phi_w(c1,e1,v1,t1) - b1 * d2 * phi_w(c1,e2,v1,t1) &
5783                  - b2 * d1 * phi_w(c2,e1,v1,t1) + b2 * d2 * phi_w(c2,e2,v1,t1)
5784          v1xysq  = v1xysq * urms**2 / t1
5785          vrms1xy = SQRT( v1xysq )
5786
5787          v2xysq  = b1 * d1 * phi_w(c1,e1,v2,t2) - b1 * d2 * phi_w(c1,e2,v2,t2) &
5788                  - b2 * d1 * phi_w(c2,e1,v2,t2) + b2 * d2 * phi_w(c2,e2,v2,t2)
5789          v2xysq  = v2xysq * urms**2 / t2
5790          vrms2xy = SQRT( v2xysq )
5791
5792          IF ( winf(i) >= winf(j) )  THEN
5793             v1 = winf(i)
5794             t1 = tau(i)
5795             v2 = winf(j)
5796             t2 = tau(j)
5797          ELSE
5798             v1 = winf(j)
5799             t1 = tau(j)
5800             v2 = winf(i)
5801             t2 = tau(i)
5802          ENDIF
5803
5804          v1v2xy   =  b1 * d1 * zhi(c1,e1,v1,t1,v2,t2) - &
5805                      b1 * d2 * zhi(c1,e2,v1,t1,v2,t2) - &
5806                      b2 * d1 * zhi(c2,e1,v1,t1,v2,t2) + &
5807                      b2 * d2* zhi(c2,e2,v1,t1,v2,t2)
5808          fr       = d1 * EXP( -rrp / e1 ) - d2 * EXP( -rrp / e2 )
5809          v1v2xy   = v1v2xy * fr * urms**2 / tau(i) / tau(j)
5810          wrtur2xy = vrms1xy**2 + vrms2xy**2 - 2.0_wp * v1v2xy
5811          IF ( wrtur2xy < 0.0_wp )  wrtur2xy = 0.0_wp
5812          wrgrav2  = pi / 8.0_wp * ( winf(j) - winf(i) )**2
5813          wrfin    = SQRT( ( 2.0_wp / pi ) * ( wrtur2xy + wrgrav2) )
5814
5815!
5816!--       Calculate radial distribution function (grfin)
5817          IF ( st(j) > st(i) )  THEN
5818             sst = st(j)
5819          ELSE
5820             sst = st(i)
5821          ENDIF
5822
5823          xx = -0.1988_wp * sst**4 + 1.5275_wp * sst**3 - 4.2942_wp *       &
5824                sst**2 + 5.3406_wp * sst
5825          IF ( xx < 0.0_wp )  xx = 0.0_wp
5826          yy = 0.1886_wp * EXP( 20.306_wp / lambda_re )
5827
5828          c1_gr  =  xx / ( g / vk * tauk )**yy
5829
5830          ao_gr  = ao + ( pi / 8.0_wp) * ( g / vk * tauk )**2
5831          fao_gr = 20.115_wp * SQRT( ao_gr / lambda_re )
5832          rc     = SQRT( fao_gr * ABS( st(j) - st(i) ) ) * eta
5833
5834          grfin  = ( ( eta**2 + rc**2 ) / ( rrp**2 + rc**2) )**( c1_gr*0.5_wp )
5835          IF ( grfin < 1.0_wp )  grfin = 1.0_wp
5836
5837!
5838!--       Calculate general collection kernel (without the consideration of
5839!--       collection efficiencies)
5840          gck(i,j) = 2.0_wp * pi * rrp**2 * wrfin * grfin
5841          gck(j,i) = gck(i,j)
5842
5843       ENDDO
5844    ENDDO
5845
5846 END SUBROUTINE turbsd
5847
5848 REAL(wp) FUNCTION phi_w( a, b, vsett, tau0 )
5849!
5850!-- Function used in the Ayala et al. (2008) analytical model for turbulent
5851!-- effects on the collision kernel
5852   
5853
5854    REAL(wp) ::  a     !<
5855    REAL(wp) ::  aa1   !<
5856    REAL(wp) ::  b     !<
5857    REAL(wp) ::  tau0  !<
5858    REAL(wp) ::  vsett !<
5859
5860    aa1 = 1.0_wp / tau0 + 1.0_wp / a + vsett / b
5861    phi_w = 1.0_wp / aa1  - 0.5_wp * vsett / b / aa1**2
5862
5863 END FUNCTION phi_w
5864
5865 REAL(wp) FUNCTION zhi( a, b, vsett1, tau1, vsett2, tau2 )
5866!
5867!-- Function used in the Ayala et al. (2008) analytical model for turbulent
5868!-- effects on the collision kernel
5869
5870    REAL(wp) ::  a      !<
5871    REAL(wp) ::  aa1    !<
5872    REAL(wp) ::  aa2    !<
5873    REAL(wp) ::  aa3    !<
5874    REAL(wp) ::  aa4    !<
5875    REAL(wp) ::  aa5    !<
5876    REAL(wp) ::  aa6    !<
5877    REAL(wp) ::  b      !<
5878    REAL(wp) ::  tau1   !<
5879    REAL(wp) ::  tau2   !<
5880    REAL(wp) ::  vsett1 !<
5881    REAL(wp) ::  vsett2 !<
5882
5883    aa1 = vsett2 / b - 1.0_wp / tau2 - 1.0_wp / a
5884    aa2 = vsett1 / b + 1.0_wp / tau1 + 1.0_wp / a
5885    aa3 = ( vsett1 - vsett2 ) / b + 1.0_wp / tau1 + 1.0_wp / tau2
5886    aa4 = ( vsett2 / b )**2 - ( 1.0_wp / tau2 + 1.0_wp / a )**2
5887    aa5 = vsett2 / b + 1.0_wp / tau2 + 1.0_wp / a
5888    aa6 = 1.0_wp / tau1 - 1.0_wp / a + ( 1.0_wp / tau2 + 1.0_wp / a) *      &
5889          vsett1 / vsett2
5890    zhi = (1.0_wp / aa1 - 1.0_wp / aa2 ) * ( vsett1 - vsett2 ) * 0.5_wp /   &
5891          b / aa3**2 + ( 4.0_wp / aa4 - 1.0_wp / aa5**2 - 1.0_wp / aa1**2 ) &
5892          * vsett2 * 0.5_wp / b /aa6 + ( 2.0_wp * ( b / aa2 - b / aa1 ) -   &
5893          vsett1 / aa2**2 + vsett2 / aa1**2 ) * 0.5_wp / b / aa3
5894
5895 END FUNCTION zhi
5896
5897
5898!------------------------------------------------------------------------------!
5899! Description:
5900! ------------
5901!> Parameterization of terminal velocity following Rogers et al. (1993, J. Appl.
5902!> Meteorol.)
5903!------------------------------------------------------------------------------!
5904 SUBROUTINE fallg
5905
5906    INTEGER(iwp) ::  j                            !<
5907
5908    REAL(wp), PARAMETER ::  k_cap_rog = 4.0_wp    !< parameter
5909    REAL(wp), PARAMETER ::  k_low_rog = 12.0_wp   !< parameter
5910    REAL(wp), PARAMETER ::  a_rog     = 9.65_wp   !< parameter
5911    REAL(wp), PARAMETER ::  b_rog     = 10.43_wp  !< parameter
5912    REAL(wp), PARAMETER ::  c_rog     = 0.6_wp    !< parameter
5913    REAL(wp), PARAMETER ::  d0_rog    = 0.745_wp  !< seperation diameter
5914
5915    REAL(wp)            ::  diameter              !< droplet diameter in mm
5916
5917
5918    DO  j = 1, radius_classes
5919
5920       diameter = radclass(j) * 2000.0_wp
5921
5922       IF ( diameter <= d0_rog )  THEN
5923          winf(j) = k_cap_rog * diameter * ( 1.0_wp -                       &
5924                                             EXP( -k_low_rog * diameter ) )
5925       ELSE
5926          winf(j) = a_rog - b_rog * EXP( -c_rog * diameter )
5927       ENDIF
5928
5929    ENDDO
5930
5931 END SUBROUTINE fallg
5932
5933
5934!------------------------------------------------------------------------------!
5935! Description:
5936! ------------
5937!> Interpolation of collision efficiencies (Hall, 1980, J. Atmos. Sci.)
5938!------------------------------------------------------------------------------!
5939 SUBROUTINE effic
5940 
5941    INTEGER(iwp) ::  i  !<
5942    INTEGER(iwp) ::  iq !<
5943    INTEGER(iwp) ::  ir !<
5944    INTEGER(iwp) ::  j  !<
5945    INTEGER(iwp) ::  k  !<
5946
5947    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ira !<
5948
5949    LOGICAL, SAVE ::  first = .TRUE. !<
5950
5951    REAL(wp) ::  ek              !<
5952    REAL(wp) ::  particle_radius !<
5953    REAL(wp) ::  pp              !<
5954    REAL(wp) ::  qq              !<
5955    REAL(wp) ::  rq              !<
5956
5957    REAL(wp), DIMENSION(1:21), SAVE ::  rat        !<
5958   
5959    REAL(wp), DIMENSION(1:15), SAVE ::  r0         !<
5960   
5961    REAL(wp), DIMENSION(1:15,1:21), SAVE ::  ecoll !<
5962
5963!
5964!-- Initial assignment of constants
5965    IF ( first )  THEN
5966
5967      first = .FALSE.
5968      r0  = (/   6.0_wp,   8.0_wp,  10.0_wp, 15.0_wp,  20.0_wp,  25.0_wp,   &
5969                30.0_wp,  40.0_wp,  50.0_wp, 60.0_wp,  70.0_wp, 100.0_wp,   &
5970               150.0_wp, 200.0_wp, 300.0_wp /)
5971
5972      rat = (/ 0.00_wp, 0.05_wp, 0.10_wp, 0.15_wp, 0.20_wp, 0.25_wp,        &
5973               0.30_wp, 0.35_wp, 0.40_wp, 0.45_wp, 0.50_wp, 0.55_wp,        &
5974               0.60_wp, 0.65_wp, 0.70_wp, 0.75_wp, 0.80_wp, 0.85_wp,        &
5975               0.90_wp, 0.95_wp, 1.00_wp /)
5976
5977      ecoll(:,1)  = (/ 0.001_wp, 0.001_wp, 0.001_wp, 0.001_wp, 0.001_wp,    &
5978                       0.001_wp, 0.001_wp, 0.001_wp, 0.001_wp, 0.001_wp,    &
5979                       0.001_wp, 0.001_wp, 0.001_wp, 0.001_wp, 0.001_wp /)
5980      ecoll(:,2)  = (/ 0.003_wp, 0.003_wp, 0.003_wp, 0.004_wp, 0.005_wp,    &
5981                       0.005_wp, 0.005_wp, 0.010_wp, 0.100_wp, 0.050_wp,    &
5982                       0.200_wp, 0.500_wp, 0.770_wp, 0.870_wp, 0.970_wp /)
5983      ecoll(:,3)  = (/ 0.007_wp, 0.007_wp, 0.007_wp, 0.008_wp, 0.009_wp,    &
5984                       0.010_wp, 0.010_wp, 0.070_wp, 0.400_wp, 0.430_wp,    &
5985                       0.580_wp, 0.790_wp, 0.930_wp, 0.960_wp, 1.000_wp /)
5986      ecoll(:,4)  = (/ 0.009_wp, 0.009_wp, 0.009_wp, 0.012_wp, 0.015_wp,    &
5987                       0.010_wp, 0.020_wp, 0.280_wp, 0.600_wp, 0.640_wp,    &
5988                       0.750_wp, 0.910_wp, 0.970_wp, 0.980_wp, 1.000_wp /)
5989      ecoll(:,5)  = (/ 0.014_wp, 0.014_wp, 0.014_wp, 0.015_wp, 0.016_wp,    &
5990                       0.030_wp, 0.060_wp, 0.500_wp, 0.700_wp, 0.770_wp,    &
5991                       0.840_wp, 0.950_wp, 0.970_wp, 1.000_wp, 1.000_wp /)
5992      ecoll(:,6)  = (/ 0.017_wp, 0.017_wp, 0.017_wp, 0.020_wp, 0.022_wp,    &
5993                       0.060_wp, 0.100_wp, 0.620_wp, 0.780_wp, 0.840_wp,    &
5994                       0.880_wp, 0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
5995      ecoll(:,7)  = (/ 0.030_wp, 0.030_wp, 0.024_wp, 0.022_wp, 0.032_wp,    &
5996                       0.062_wp, 0.200_wp, 0.680_wp, 0.830_wp, 0.870_wp,    &
5997                       0.900_wp, 0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
5998      ecoll(:,8)  = (/ 0.025_wp, 0.025_wp, 0.025_wp, 0.036_wp, 0.043_wp,    &
5999                       0.130_wp, 0.270_wp, 0.740_wp, 0.860_wp, 0.890_wp,    &
6000                       0.920_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6001      ecoll(:,9)  = (/ 0.027_wp, 0.027_wp, 0.027_wp, 0.040_wp, 0.052_wp,    &
6002                       0.200_wp, 0.400_wp, 0.780_wp, 0.880_wp, 0.900_wp,    &
6003                       0.940_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6004      ecoll(:,10) = (/ 0.030_wp, 0.030_wp, 0.030_wp, 0.047_wp, 0.064_wp,    &
6005                       0.250_wp, 0.500_wp, 0.800_wp, 0.900_wp, 0.910_wp,    &
6006                       0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6007      ecoll(:,11) = (/ 0.040_wp, 0.040_wp, 0.033_wp, 0.037_wp, 0.068_wp,    &
6008                       0.240_wp, 0.550_wp, 0.800_wp, 0.900_wp, 0.910_wp,    &
6009                       0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6010      ecoll(:,12) = (/ 0.035_wp, 0.035_wp, 0.035_wp, 0.055_wp, 0.079_wp,    &
6011                       0.290_wp, 0.580_wp, 0.800_wp, 0.900_wp, 0.910_wp,    &
6012                       0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6013      ecoll(:,13) = (/ 0.037_wp, 0.037_wp, 0.037_wp, 0.062_wp, 0.082_wp,    &
6014                       0.290_wp, 0.590_wp, 0.780_wp, 0.900_wp, 0.910_wp,    &
6015                       0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6016      ecoll(:,14) = (/ 0.037_wp, 0.037_wp, 0.037_wp, 0.060_wp, 0.080_wp,    &
6017                       0.290_wp, 0.580_wp, 0.770_wp, 0.890_wp, 0.910_wp,    &
6018                       0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6019      ecoll(:,15) = (/ 0.037_wp, 0.037_wp, 0.037_wp, 0.041_wp, 0.075_wp,    &
6020                       0.250_wp, 0.540_wp, 0.760_wp, 0.880_wp, 0.920_wp,    &
6021                       0.950_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6022      ecoll(:,16) = (/ 0.037_wp, 0.037_wp, 0.037_wp, 0.052_wp, 0.067_wp,    &
6023                       0.250_wp, 0.510_wp, 0.770_wp, 0.880_wp, 0.930_wp,    &
6024                       0.970_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6025      ecoll(:,17) = (/ 0.037_wp, 0.037_wp, 0.037_wp, 0.047_wp, 0.057_wp,    &
6026                       0.250_wp, 0.490_wp, 0.770_wp, 0.890_wp, 0.950_wp,    &
6027                       1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp, 1.000_wp /)
6028      ecoll(:,18) = (/ 0.036_wp, 0.036_wp, 0.036_wp, 0.042_wp, 0.048_wp,    &
6029                       0.230_wp, 0.470_wp, 0.780_wp, 0.920_wp, 1.000_wp,    &
6030                       1.020_wp, 1.020_wp, 1.020_wp, 1.020_wp, 1.020_wp /)
6031      ecoll(:,19) = (/ 0.040_wp, 0.040_wp, 0.035_wp, 0.033_wp, 0.040_wp,    &
6032                       0.112_wp, 0.450_wp, 0.790_wp, 1.010_wp, 1.030_wp,    &
6033                       1.040_wp, 1.040_wp, 1.040_wp, 1.040_wp, 1.040_wp /)
6034      ecoll(:,20) = (/ 0.033_wp, 0.033_wp, 0.033_wp, 0.033_wp, 0.033_wp,    &
6035                       0.119_wp, 0.470_wp, 0.950_wp, 1.300_wp, 1.700_wp,    &
6036                       2.300_wp, 2.300_wp, 2.300_wp, 2.300_wp, 2.300_wp /)
6037      ecoll(:,21) = (/ 0.027_wp, 0.027_wp, 0.027_wp, 0.027_wp, 0.027_wp,    &
6038                       0.125_wp, 0.520_wp, 1.400_wp, 2.300_wp, 3.000_wp,    &
6039                       4.000_wp, 4.000_wp, 4.000_wp, 4.000_wp, 4.000_wp /)
6040    ENDIF
6041
6042!
6043!-- Calculate the radius class index of particles with respect to array r
6044!-- Radius has to be in microns
6045    ALLOCATE( ira(1:radius_classes) )
6046    DO  j = 1, radius_classes
6047       particle_radius = radclass(j) * 1.0E6_wp
6048       DO  k = 1, 15
6049          IF ( particle_radius < r0(k) )  THEN
6050             ira(j) = k
6051             EXIT
6052          ENDIF
6053       ENDDO
6054       IF ( particle_radius >= r0(15) )  ira(j) = 16
6055    ENDDO
6056
6057!
6058!-- Two-dimensional linear interpolation of the collision efficiency.
6059!-- Radius has to be in microns
6060    DO  j = 1, radius_classes
6061       DO  i = 1, j
6062
6063          ir = MAX( ira(i), ira(j) )
6064          rq = MIN( radclass(i) / radclass(j), radclass(j) / radclass(i) )
6065          iq = INT( rq * 20 ) + 1
6066          iq = MAX( iq , 2)
6067
6068          IF ( ir < 16 )  THEN
6069             IF ( ir >= 2 )  THEN
6070                pp = ( ( MAX( radclass(j), radclass(i) ) * 1.0E6_wp ) -     &
6071                       r0(ir-1) ) / ( r0(ir) - r0(ir-1) )
6072                qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
6073                ec(j,i) = ( 1.0_wp - pp ) * ( 1.0_wp - qq )                 &
6074                          * ecoll(ir-1,iq-1)                                &
6075                          + pp * ( 1.0_wp - qq ) * ecoll(ir,iq-1)           &
6076                          + qq * ( 1.0_wp - pp ) * ecoll(ir-1,iq)           &
6077                          + pp * qq * ecoll(ir,iq)
6078             ELSE
6079                qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
6080                ec(j,i) = ( 1.0_wp - qq ) * ecoll(1,iq-1) + qq * ecoll(1,iq)
6081             ENDIF
6082          ELSE
6083             qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
6084             ek = ( 1.0_wp - qq ) * ecoll(15,iq-1) + qq * ecoll(15,iq)
6085             ec(j,i) = MIN( ek, 1.0_wp )
6086          ENDIF
6087
6088          IF ( ec(j,i) < 1.0E-20_wp )  ec(j,i) = 0.0_wp
6089
6090          ec(i,j) = ec(j,i)
6091
6092       ENDDO
6093    ENDDO
6094
6095    DEALLOCATE( ira )
6096
6097 END SUBROUTINE effic
6098
6099
6100!------------------------------------------------------------------------------!
6101! Description:
6102! ------------
6103!> Interpolation of turbulent enhancement factor for collision efficencies
6104!> following Wang and Grabowski (2009, Atmos. Sci. Let.)
6105!------------------------------------------------------------------------------!
6106 SUBROUTINE turb_enhance_eff
6107
6108    INTEGER(iwp) :: i  !<
6109    INTEGER(iwp) :: iq !<
6110    INTEGER(iwp) :: ir !<
6111    INTEGER(iwp) :: j  !<
6112    INTEGER(iwp) :: k  !<
6113    INTEGER(iwp) :: kk !<
6114
6115    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ira !<
6116   
6117    LOGICAL, SAVE ::  first = .TRUE. !<
6118
6119    REAL(wp) ::  particle_radius !<
6120    REAL(wp) ::  pp              !<
6121    REAL(wp) ::  qq              !<
6122    REAL(wp) ::  rq              !<
6123    REAL(wp) ::  y1              !<
6124    REAL(wp) ::  y2              !<
6125    REAL(wp) ::  y3              !<
6126
6127    REAL(wp), DIMENSION(1:11), SAVE ::  rat           !<
6128    REAL(wp), DIMENSION(1:7), SAVE  ::  r0            !<
6129   
6130    REAL(wp), DIMENSION(1:7,1:11), SAVE ::  ecoll_100 !<
6131    REAL(wp), DIMENSION(1:7,1:11), SAVE ::  ecoll_400 !<
6132
6133!
6134!-- Initial assignment of constants
6135    IF ( first )  THEN
6136
6137       first = .FALSE.
6138
6139       r0  = (/  10.0_wp, 20.0_wp, 30.0_wp, 40.0_wp, 50.0_wp, 60.0_wp,  &
6140                100.0_wp /)
6141
6142       rat = (/ 0.0_wp, 0.1_wp, 0.2_wp, 0.3_wp, 0.4_wp, 0.5_wp, 0.6_wp, &
6143                0.7_wp, 0.8_wp, 0.9_wp, 1.0_wp /)
6144!
6145!--    Tabulated turbulent enhancement factor at 100 cm**2/s**3
6146       ecoll_100(:,1)  = (/  1.74_wp,   1.74_wp,   1.773_wp, 1.49_wp,  &
6147                             1.207_wp,  1.207_wp,  1.0_wp /)
6148       ecoll_100(:,2)  = (/  1.46_wp,   1.46_wp,   1.421_wp, 1.245_wp, &
6149                             1.069_wp,  1.069_wp,  1.0_wp /)
6150       ecoll_100(:,3)  = (/  1.32_wp,   1.32_wp,   1.245_wp, 1.123_wp, &
6151                             1.000_wp,  1.000_wp,  1.0_wp /)
6152       ecoll_100(:,4)  = (/  1.250_wp,  1.250_wp,  1.148_wp, 1.087_wp, &
6153                             1.025_wp,  1.025_wp,  1.0_wp /)
6154       ecoll_100(:,5)  = (/  1.186_wp,  1.186_wp,  1.066_wp, 1.060_wp, &
6155                             1.056_wp,  1.056_wp,  1.0_wp /)
6156       ecoll_100(:,6)  = (/  1.045_wp,  1.045_wp,  1.000_wp, 1.014_wp, &
6157                             1.028_wp,  1.028_wp,  1.0_wp /)
6158       ecoll_100(:,7)  = (/  1.070_wp,  1.070_wp,  1.030_wp, 1.038_wp, &
6159                             1.046_wp,  1.046_wp,  1.0_wp /)
6160       ecoll_100(:,8)  = (/  1.000_wp,  1.000_wp,  1.054_wp, 1.042_wp, &
6161                             1.029_wp,  1.029_wp,  1.0_wp /)
6162       ecoll_100(:,9)  = (/  1.223_wp,  1.223_wp,  1.117_wp, 1.069_wp, &
6163                             1.021_wp,  1.021_wp,  1.0_wp /)
6164       ecoll_100(:,10) = (/  1.570_wp,  1.570_wp,  1.244_wp, 1.166_wp, &
6165                             1.088_wp,  1.088_wp,  1.0_wp /)
6166       ecoll_100(:,11) = (/ 20.3_wp,   20.3_wp,   14.6_wp,   8.61_wp,  &
6167                             2.60_wp,   2.60_wp,   1.0_wp /)
6168!
6169!--    Tabulated turbulent enhancement factor at 400 cm**2/s**3
6170       ecoll_400(:,1)  = (/  4.976_wp,  4.976_wp,  3.593_wp,  2.519_wp, &
6171                             1.445_wp,  1.445_wp,  1.0_wp /)
6172       ecoll_400(:,2)  = (/  2.984_wp,  2.984_wp,  2.181_wp,  1.691_wp, &
6173                             1.201_wp,  1.201_wp,  1.0_wp /)
6174       ecoll_400(:,3)  = (/  1.988_wp,  1.988_wp,  1.475_wp,  1.313_wp, &
6175                             1.150_wp,  1.150_wp,  1.0_wp /)
6176       ecoll_400(:,4)  = (/  1.490_wp,  1.490_wp,  1.187_wp,  1.156_wp, &
6177                             1.126_wp,  1.126_wp,  1.0_wp /)
6178       ecoll_400(:,5)  = (/  1.249_wp,  1.249_wp,  1.088_wp,  1.090_wp, &
6179                             1.092_wp,  1.092_wp,  1.0_wp /)
6180       ecoll_400(:,6)  = (/  1.139_wp,  1.139_wp,  1.130_wp,  1.091_wp, &
6181                             1.051_wp,  1.051_wp,  1.0_wp /)
6182       ecoll_400(:,7)  = (/  1.220_wp,  1.220_wp,  1.190_wp,  1.138_wp, &
6183                             1.086_wp,  1.086_wp,  1.0_wp /)
6184       ecoll_400(:,8)  = (/  1.325_wp,  1.325_wp,  1.267_wp,  1.165_wp, &
6185                             1.063_wp,  1.063_wp,  1.0_wp /)
6186       ecoll_400(:,9)  = (/  1.716_wp,  1.716_wp,  1.345_wp,  1.223_wp, &
6187                             1.100_wp,  1.100_wp,  1.0_wp /)
6188       ecoll_400(:,10) = (/  3.788_wp,  3.788_wp,  1.501_wp,  1.311_wp, &
6189                             1.120_wp,  1.120_wp,  1.0_wp /)
6190       ecoll_400(:,11) = (/ 36.52_wp,  36.52_wp,  19.16_wp,  22.80_wp,  &
6191                            26.0_wp,   26.0_wp,    1.0_wp /)
6192
6193    ENDIF
6194
6195!
6196!-- Calculate the radius class index of particles with respect to array r0
6197!-- The droplet radius has to be given in microns.
6198    ALLOCATE( ira(1:radius_classes) )
6199
6200    DO  j = 1, radius_classes
6201       particle_radius = radclass(j) * 1.0E6_wp
6202       DO  k = 1, 7
6203          IF ( particle_radius < r0(k) )  THEN
6204             ira(j) = k
6205             EXIT
6206          ENDIF
6207       ENDDO
6208       IF ( particle_radius >= r0(7) )  ira(j) = 8
6209    ENDDO
6210
6211!
6212!-- Two-dimensional linear interpolation of the turbulent enhancement factor.
6213!-- The droplet radius has to be given in microns.
6214    DO  j =  1, radius_classes
6215       DO  i = 1, j
6216
6217          ir = MAX( ira(i), ira(j) )
6218          rq = MIN( radclass(i) / radclass(j), radclass(j) / radclass(i) )
6219
6220          DO  kk = 2, 11
6221             IF ( rq <= rat(kk) )  THEN
6222                iq = kk
6223                EXIT
6224             ENDIF
6225          ENDDO
6226
6227          y1 = 1.0_wp  ! turbulent enhancement factor at 0 m**2/s**3
6228
6229          IF ( ir < 8 )  THEN
6230             IF ( ir >= 2 )  THEN
6231                pp = ( MAX( radclass(j), radclass(i) ) * 1.0E6_wp -  &
6232                       r0(ir-1) ) / ( r0(ir) - r0(ir-1) )
6233                qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
6234                y2 = ( 1.0_wp - pp ) * ( 1.0_wp - qq ) * ecoll_100(ir-1,iq-1) + &
6235                             pp * ( 1.0_wp - qq ) * ecoll_100(ir,iq-1)        + &
6236                             qq * ( 1.0_wp - pp ) * ecoll_100(ir-1,iq)        + &
6237                             pp * qq              * ecoll_100(ir,iq)
6238                y3 = ( 1.0-pp ) * ( 1.0_wp - qq ) * ecoll_400(ir-1,iq-1)      + &
6239                             pp * ( 1.0_wp - qq ) * ecoll_400(ir,iq-1)        + &
6240                             qq * ( 1.0_wp - pp ) * ecoll_400(ir-1,iq)        + &
6241                             pp * qq              * ecoll_400(ir,iq)
6242             ELSE
6243                qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
6244                y2 = ( 1.0_wp - qq ) * ecoll_100(1,iq-1) + qq * ecoll_100(1,iq)
6245                y3 = ( 1.0_wp - qq ) * ecoll_400(1,iq-1) + qq * ecoll_400(1,iq)
6246             ENDIF
6247          ELSE
6248             qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
6249             y2 = ( 1.0_wp - qq ) * ecoll_100(7,iq-1) + qq * ecoll_100(7,iq)
6250             y3 = ( 1.0_wp - qq ) * ecoll_400(7,iq-1) + qq * ecoll_400(7,iq)
6251          ENDIF
6252!
6253!--       Linear interpolation of turbulent enhancement factor
6254          IF ( epsilon_collision <= 0.01_wp )  THEN
6255             ecf(j,i) = ( epsilon_collision - 0.01_wp ) / ( 0.0_wp  - 0.01_wp ) * y1 &
6256                      + ( epsilon_collision - 0.0_wp  ) / ( 0.01_wp - 0.0_wp  ) * y2
6257          ELSEIF ( epsilon_collision <= 0.06_wp )  THEN
6258             ecf(j,i) = ( epsilon_collision - 0.04_wp ) / ( 0.01_wp - 0.04_wp ) * y2 &
6259                      + ( epsilon_collision - 0.01_wp ) / ( 0.04_wp - 0.01_wp ) * y3
6260          ELSE
6261             ecf(j,i) = ( 0.06_wp - 0.04_wp ) / ( 0.01_wp - 0.04_wp ) * y2 &
6262                      + ( 0.06_wp - 0.01_wp ) / ( 0.04_wp - 0.01_wp ) * y3
6263          ENDIF
6264
6265          IF ( ecf(j,i) < 1.0_wp )  ecf(j,i) = 1.0_wp
6266
6267          ecf(i,j) = ecf(j,i)
6268
6269       ENDDO
6270    ENDDO
6271
6272 END SUBROUTINE turb_enhance_eff
6273 
6274 
6275 !------------------------------------------------------------------------------!
6276! Description:
6277! ------------
6278! This routine is a part of the Lagrangian particle model. Super droplets which
6279! fulfill certain criterion's (e.g. a big weighting factor and a large radius)
6280! can be split into several super droplets with a reduced number of
6281! represented particles of every super droplet. This mechanism ensures an
6282! improved representation of the right tail of the drop size distribution with
6283! a feasible amount of computational costs. The limits of particle creation
6284! should be chosen carefully! The idea of this algorithm is based on
6285! Unterstrasser and Soelch, 2014.
6286!------------------------------------------------------------------------------!
6287 SUBROUTINE lpm_splitting
6288
6289    INTEGER(iwp) ::  i                !<
6290    INTEGER(iwp) ::  j                !<
6291    INTEGER(iwp) ::  jpp              !<
6292    INTEGER(iwp) ::  k                !<
6293    INTEGER(iwp) ::  n                !<
6294    INTEGER(iwp) ::  new_particles_gb !< counter of created particles within one grid box
6295    INTEGER(iwp) ::  new_size         !< new particle array size
6296    INTEGER(iwp) ::  np               !<
6297    INTEGER(iwp) ::  old_size         !< old particle array size
6298   
6299    INTEGER(iwp), PARAMETER ::  n_max = 100 !< number of radii bin for splitting functions   
6300   
6301    LOGICAL ::  first_loop_stride_sp = .TRUE. !< flag to calculate constants only once
6302
6303    REAL(wp) ::  diameter                 !< diameter of droplet
6304    REAL(wp) ::  dlog                     !< factor for DSD calculation
6305    REAL(wp) ::  factor_volume_to_mass    !< pre calculate factor volume to mass
6306    REAL(wp) ::  lambda                   !< slope parameter of gamma-distribution
6307    REAL(wp) ::  lwc                      !< liquid water content of grid box
6308    REAL(wp) ::  lwc_total                !< average liquid water content of cloud
6309    REAL(wp) ::  m1                       !< first moment of DSD
6310    REAL(wp) ::  m1_total                 !< average over all PEs of first moment of DSD
6311    REAL(wp) ::  m2                       !< second moment of DSD
6312    REAL(wp) ::  m2_total                 !< average average over all PEs second moment of DSD
6313    REAL(wp) ::  m3                       !< third moment of DSD
6314    REAL(wp) ::  m3_total                 !< average average over all PEs third moment of DSD
6315    REAL(wp) ::  mu                       !< spectral shape parameter of gamma distribution
6316    REAL(wp) ::  nrclgb                   !< number of cloudy grid boxes (ql >= 1.0E-5 kg/kg)
6317    REAL(wp) ::  nrclgb_total             !< average over all PEs of number of cloudy grid boxes
6318    REAL(wp) ::  nr                       !< number concentration of cloud droplets
6319    REAL(wp) ::  nr_total                 !< average over all PEs of number of cloudy grid boxes
6320    REAL(wp) ::  nr0                      !< intercept parameter of gamma distribution
6321    REAL(wp) ::  pirho_l                  !< pi * rho_l / 6.0
6322    REAL(wp) ::  ql_crit = 1.0E-5_wp      !< threshold lwc for cloudy grid cells
6323                                          !< (Siebesma et al 2003, JAS, 60)
6324    REAL(wp) ::  rm                       !< volume averaged mean radius
6325    REAL(wp) ::  rm_total                 !< average over all PEs of volume averaged mean radius
6326    REAL(wp) ::  r_min = 1.0E-6_wp        !< minimum radius of approximated spectra
6327    REAL(wp) ::  r_max = 1.0E-3_wp        !< maximum radius of approximated spectra
6328    REAL(wp) ::  sigma_log = 1.5_wp       !< standard deviation of the LOG-distribution
6329    REAL(wp) ::  zeta                     !< Parameter for DSD calculation of Seifert
6330
6331    REAL(wp), DIMENSION(0:n_max-1) ::  an_spl     !< size dependent critical weight factor
6332    REAL(wp), DIMENSION(0:n_max-1) ::  r_bin_mid  !< mass weighted mean radius of a bin
6333    REAL(wp), DIMENSION(0:n_max)   ::  r_bin      !< boundaries of a radius bin
6334   
6335    TYPE(particle_type) ::  tmp_particle   !< temporary particle TYPE
6336
6337    CALL cpu_log( log_point_s(80), 'lpm_splitting', 'start' )
6338
6339    IF ( first_loop_stride_sp )  THEN
6340       IF ( i_splitting_mode == 2  .OR.  i_splitting_mode == 3 )  THEN
6341          dlog   = ( LOG10(r_max) - LOG10(r_min) ) / ( n_max - 1 )
6342          DO  i = 0, n_max-1
6343             r_bin(i) = 10.0_wp**( LOG10(r_min) + i * dlog - 0.5_wp * dlog )
6344             r_bin_mid(i) = 10.0_wp**( LOG10(r_min) + i * dlog )
6345          ENDDO
6346          r_bin(n_max) = 10.0_wp**( LOG10(r_min) + n_max * dlog - 0.5_wp * dlog )
6347       ENDIF   
6348       factor_volume_to_mass =  4.0_wp / 3.0_wp * pi * rho_l
6349       pirho_l  = pi * rho_l / 6.0_wp
6350       IF ( weight_factor_split == -1.0_wp )  THEN
6351          weight_factor_split = 0.1_wp * initial_weighting_factor 
6352       ENDIF
6353    ENDIF
6354
6355
6356    IF ( i_splitting_mode == 1 )  THEN
6357
6358       DO  i = nxl, nxr
6359          DO  j = nys, nyn
6360             DO  k = nzb+1, nzt
6361
6362                new_particles_gb = 0
6363                number_of_particles = prt_count(k,j,i)
6364                IF ( number_of_particles <= 0  .OR.                            & 
6365                     ql(k,j,i) < ql_crit )  CYCLE
6366                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
6367!
6368!--             Start splitting operations. Each particle is checked if it
6369!--             fulfilled the splitting criterion's. In splitting mode 'const'   
6370!--             a critical radius  (radius_split) a critical weighting factor
6371!--             (weight_factor_split) and a splitting factor (splitting_factor)
6372!--             must  be prescribed (see particle_parameters). Super droplets
6373!--             which have a larger radius and larger weighting factor are split
6374!--             into 'splitting_factor' super droplets. Therefore, the weighting
6375!--             factor of  the super droplet and all created clones is reduced
6376!--             by the factor of 'splitting_factor'.
6377                DO  n = 1, number_of_particles
6378                   IF ( particles(n)%particle_mask  .AND.                      &
6379                        particles(n)%radius >= radius_split  .AND.             & 
6380                        particles(n)%weight_factor >= weight_factor_split )    &
6381                   THEN
6382!
6383!--                   Calculate the new number of particles.
6384                      new_size = prt_count(k,j,i) + splitting_factor - 1
6385!
6386!--                   Cycle if maximum number of particles per grid box
6387!--                   is greater than the allowed maximum number.
6388                      IF ( new_size >= max_number_particles_per_gridbox )  CYCLE
6389!
6390!--                   Reallocate particle array if necessary.
6391                      IF ( new_size > SIZE(particles) )  THEN
6392                         CALL realloc_particles_array(i,j,k,new_size)
6393                      ENDIF
6394                      old_size = prt_count(k,j,i)
6395!
6396!--                   Calculate new weighting factor.
6397                      particles(n)%weight_factor =  & 
6398                         particles(n)%weight_factor / splitting_factor
6399                      tmp_particle = particles(n)
6400!
6401!--                   Create splitting_factor-1 new particles.
6402                      DO  jpp = 1, splitting_factor-1
6403                         grid_particles(k,j,i)%particles(jpp+old_size) =       & 
6404                            tmp_particle
6405                      ENDDO 
6406                      new_particles_gb = new_particles_gb + splitting_factor - 1
6407!   
6408!--                   Save the new number of super droplets for every grid box.
6409                      prt_count(k,j,i) = prt_count(k,j,i) +                    &
6410                                         splitting_factor - 1
6411                   ENDIF
6412                ENDDO
6413
6414             ENDDO
6415          ENDDO
6416       ENDDO
6417
6418    ELSEIF ( i_splitting_mode == 2 )  THEN 
6419!
6420!--    Initialize summing variables.
6421       lwc          = 0.0_wp
6422       lwc_total    = 0.0_wp 
6423       m1           = 0.0_wp
6424       m1_total     = 0.0_wp
6425       m2           = 0.0_wp
6426       m2_total     = 0.0_wp
6427       m3           = 0.0_wp
6428       m3_total     = 0.0_wp
6429       nr           = 0.0_wp
6430       nrclgb       = 0.0_wp
6431       nrclgb_total = 0.0_wp
6432       nr_total     = 0.0_wp
6433       rm           = 0.0_wp
6434       rm_total     = 0.0_wp
6435
6436       DO  i = nxl, nxr
6437          DO  j = nys, nyn
6438             DO  k = nzb+1, nzt
6439                number_of_particles = prt_count(k,j,i)
6440                IF ( number_of_particles <= 0  .OR.                            & 
6441                     ql(k,j,i) < ql_crit )  CYCLE
6442                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
6443                nrclgb = nrclgb + 1.0_wp
6444!
6445!--             Calculate moments of DSD.
6446                DO  n = 1, number_of_particles
6447                   IF ( particles(n)%particle_mask  .AND.                      &
6448                        particles(n)%radius >= r_min )                         &
6449                   THEN
6450                      nr  = nr  + particles(n)%weight_factor
6451                      rm  = rm  + factor_volume_to_mass  *                     &
6452                                 particles(n)%radius**3  *                     &
6453                                 particles(n)%weight_factor
6454                      IF ( isf == 1 )  THEN           
6455                         diameter   = particles(n)%radius * 2.0_wp
6456                         lwc = lwc + factor_volume_to_mass *                   &
6457                                     particles(n)%radius**3 *                  & 
6458                                     particles(n)%weight_factor 
6459                         m1  = m1  + particles(n)%weight_factor * diameter
6460                         m2  = m2  + particles(n)%weight_factor * diameter**2
6461                         m3  = m3  + particles(n)%weight_factor * diameter**3
6462                      ENDIF
6463                   ENDIF
6464                ENDDO 
6465             ENDDO
6466          ENDDO
6467       ENDDO
6468
6469#if defined( __parallel )
6470       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
6471       CALL MPI_ALLREDUCE( nr, nr_total, 1 , &
6472       MPI_REAL, MPI_SUM, comm2d, ierr )
6473       CALL MPI_ALLREDUCE( rm, rm_total, 1 , &
6474       MPI_REAL, MPI_SUM, comm2d, ierr )
6475       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
6476       CALL MPI_ALLREDUCE( nrclgb, nrclgb_total, 1 , &
6477       MPI_REAL, MPI_SUM, comm2d, ierr )
6478       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
6479       CALL MPI_ALLREDUCE( lwc, lwc_total, 1 , &
6480       MPI_REAL, MPI_SUM, comm2d, ierr )
6481       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
6482       CALL MPI_ALLREDUCE( m1, m1_total, 1 , &
6483       MPI_REAL, MPI_SUM, comm2d, ierr )
6484       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
6485       CALL MPI_ALLREDUCE( m2, m2_total, 1 , &
6486       MPI_REAL, MPI_SUM, comm2d, ierr )
6487       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
6488       CALL MPI_ALLREDUCE( m3, m3_total, 1 , &
6489       MPI_REAL, MPI_SUM, comm2d, ierr )
6490#endif 
6491
6492!
6493!--    Calculate number concentration and mean volume averaged radius.
6494       nr_total = MERGE( nr_total / nrclgb_total,                              &
6495                         0.0_wp, nrclgb_total > 0.0_wp                         &
6496                       )
6497       rm_total = MERGE( ( rm_total /                                          &
6498                            ( nr_total * factor_volume_to_mass )               &
6499                          )**0.3333333_wp, 0.0_wp, nrclgb_total > 0.0_wp       &
6500                       )
6501!
6502!--    Check which function should be used to approximate the DSD.
6503       IF ( isf == 1 )  THEN
6504          lwc_total = MERGE( lwc_total / nrclgb_total,                         &
6505                             0.0_wp, nrclgb_total > 0.0_wp                     &
6506                           )
6507          m1_total  = MERGE( m1_total / nrclgb_total,                          &
6508                             0.0_wp, nrclgb_total > 0.0_wp                     &
6509                           )
6510          m2_total  = MERGE( m2_total / nrclgb_total,                          &
6511                             0.0_wp, nrclgb_total > 0.0_wp                     &
6512                           )
6513          m3_total  = MERGE( m3_total / nrclgb_total,                          &
6514                             0.0_wp, nrclgb_total > 0.0_wp                     &
6515                           )
6516          zeta = m1_total * m3_total / m2_total**2
6517          mu   = MAX( ( ( 1.0_wp - zeta ) * 2.0_wp + 1.0_wp ) /                &
6518                        ( zeta - 1.0_wp ), 0.0_wp                              &
6519                    )
6520
6521          lambda = ( pirho_l * nr_total / lwc_total *                          &
6522                     ( mu + 3.0_wp ) * ( mu + 2.0_wp ) * ( mu + 1.0_wp )       &
6523                   )**0.3333333_wp
6524          nr0 = nr_total / gamma( mu + 1.0_wp ) * lambda**( mu + 1.0_wp ) 
6525
6526          DO  n = 0, n_max-1
6527             diameter  = r_bin_mid(n) * 2.0_wp
6528             an_spl(n) = nr0 * diameter**mu * EXP( -lambda * diameter ) *      & 
6529                         ( r_bin(n+1) - r_bin(n) ) * 2.0_wp 
6530          ENDDO
6531       ELSEIF ( isf == 2 )  THEN
6532          DO  n = 0, n_max-1
6533             an_spl(n) = nr_total / ( SQRT( 2.0_wp * pi ) *                    &
6534                                     LOG(sigma_log) * r_bin_mid(n)             &
6535                                     ) *                                       &
6536                         EXP( -( LOG( r_bin_mid(n) / rm_total )**2 ) /         &
6537                               ( 2.0_wp * LOG(sigma_log)**2 )                  & 
6538                             ) *                                               & 
6539                         ( r_bin(n+1) - r_bin(n) )
6540          ENDDO
6541       ELSEIF( isf == 3 )  THEN
6542          DO  n = 0, n_max-1 
6543             an_spl(n) = 3.0_wp * nr_total * r_bin_mid(n)**2 / rm_total**3  *  &
6544                         EXP( - ( r_bin_mid(n)**3 / rm_total**3 ) )         *  &
6545                         ( r_bin(n+1) - r_bin(n) )
6546          ENDDO
6547       ENDIF
6548!
6549!--    Criterion to avoid super droplets with a weighting factor < 1.0.
6550       an_spl = MAX(an_spl, 1.0_wp)
6551
6552       DO  i = nxl, nxr
6553          DO  j = nys, nyn
6554             DO  k = nzb+1, nzt
6555                number_of_particles = prt_count(k,j,i)
6556                IF ( number_of_particles <= 0  .OR.                            &
6557                     ql(k,j,i) < ql_crit )  CYCLE
6558                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
6559                new_particles_gb = 0
6560!
6561!--             Start splitting operations. Each particle is checked if it
6562!--             fulfilled the splitting criterion's. In splitting mode 'cl_av'
6563!--             a critical radius (radius_split) and a splitting function must
6564!--             be prescribed (see particles_par). The critical weighting factor
6565!--             is calculated while approximating a 'gamma', 'log' or 'exp'-
6566!--             drop size distribution. In this mode the DSD is calculated as
6567!--             an average over all cloudy grid boxes. Super droplets which
6568!--             have a larger radius and larger weighting factor are split into
6569!--             'splitting_factor' super droplets. In this case the splitting
6570!--             factor is calculated of weighting factor of the super droplet
6571!--             and the approximated number concentration for droplet of such
6572!--             a size. Due to the splitting, the weighting factor of the
6573!--             super droplet and all created clones is reduced by the factor
6574!--             of 'splitting_facor'.
6575                DO  n = 1, number_of_particles
6576                   DO  np = 0, n_max-1
6577                      IF ( r_bin(np) >= radius_split  .AND.                    &
6578                           particles(n)%particle_mask  .AND.                   &
6579                           particles(n)%radius >= r_bin(np)  .AND.             &
6580                           particles(n)%radius < r_bin(np+1)  .AND.            &
6581                           particles(n)%weight_factor >= an_spl(np)  )         &
6582                      THEN
6583!
6584!--                      Calculate splitting factor
6585                         splitting_factor =                                    & 
6586                             MIN( INT( particles(n)%weight_factor /            &
6587                                        an_spl(np)                             &
6588                                     ), splitting_factor_max                   &
6589                                )
6590                         IF ( splitting_factor < 2 )  CYCLE
6591!
6592!--                      Calculate the new number of particles.
6593                         new_size = prt_count(k,j,i) + splitting_factor - 1
6594!
6595!--                      Cycle if maximum number of particles per grid box
6596!--                      is greater than the allowed maximum number.
6597                         IF ( new_size >= max_number_particles_per_gridbox )   & 
6598                         CYCLE
6599!
6600!--                      Reallocate particle array if necessary.
6601                         IF ( new_size > SIZE(particles) )  THEN
6602                            CALL realloc_particles_array(i,j,k,new_size)
6603                         ENDIF
6604                         old_size  = prt_count(k,j,i)
6605                         new_particles_gb = new_particles_gb +                 &
6606                                            splitting_factor - 1
6607!
6608!--                      Calculate new weighting factor.
6609                         particles(n)%weight_factor =                          & 
6610                            particles(n)%weight_factor / splitting_factor
6611                         tmp_particle = particles(n)
6612!
6613!--                      Create splitting_factor-1 new particles.
6614                         DO  jpp = 1, splitting_factor-1
6615                            grid_particles(k,j,i)%particles(jpp+old_size) =    &
6616                                                                    tmp_particle
6617                         ENDDO
6618!
6619!--                      Save the new number of super droplets.
6620                         prt_count(k,j,i) = prt_count(k,j,i) +                 &
6621                                            splitting_factor - 1
6622                      ENDIF
6623                   ENDDO
6624                ENDDO 
6625
6626             ENDDO
6627          ENDDO
6628       ENDDO
6629
6630    ELSEIF ( i_splitting_mode == 3 )  THEN
6631
6632       DO  i = nxl, nxr
6633          DO  j = nys, nyn
6634             DO  k = nzb+1, nzt
6635
6636!
6637!--             Initialize summing variables.
6638                lwc = 0.0_wp
6639                m1  = 0.0_wp
6640                m2  = 0.0_wp
6641                m3  = 0.0_wp
6642                nr  = 0.0_wp
6643                rm  = 0.0_wp 
6644
6645                new_particles_gb = 0
6646                number_of_particles = prt_count(k,j,i)
6647                IF ( number_of_particles <= 0  .OR.                            & 
6648                     ql(k,j,i) < ql_crit )  CYCLE
6649                particles => grid_particles(k,j,i)%particles
6650!
6651!--             Calculate moments of DSD.
6652                DO  n = 1, number_of_particles
6653                   IF ( particles(n)%particle_mask  .AND.                      &
6654                        particles(n)%radius >= r_min )                         &
6655                   THEN
6656                      nr  = nr + particles(n)%weight_factor
6657                      rm  = rm + factor_volume_to_mass  *                      &
6658                                 particles(n)%radius**3  *                     &
6659                                 particles(n)%weight_factor
6660                      IF ( isf == 1 )  THEN
6661                         diameter   = particles(n)%radius * 2.0_wp
6662                         lwc = lwc + factor_volume_to_mass *                   &
6663                                     particles(n)%radius**3 *                  &
6664                                     particles(n)%weight_factor 
6665                         m1  = m1 + particles(n)%weight_factor * diameter
6666                         m2  = m2 + particles(n)%weight_factor * diameter**2
6667                         m3  = m3 + particles(n)%weight_factor * diameter**3
6668                      ENDIF
6669                   ENDIF
6670                ENDDO
6671
6672                IF ( nr <= 0.0_wp  .OR.  rm <= 0.0_wp )  CYCLE
6673!
6674!--             Calculate mean volume averaged radius.
6675                rm = ( rm / ( nr * factor_volume_to_mass ) )**0.3333333_wp
6676!
6677!--             Check which function should be used to approximate the DSD.
6678                IF ( isf == 1 )  THEN
6679!
6680!--                Gamma size distribution to calculate 
6681!--                critical weight_factor (e.g. Marshall + Palmer, 1948).
6682                   zeta = m1 * m3 / m2**2
6683                   mu   = MAX( ( ( 1.0_wp - zeta ) * 2.0_wp + 1.0_wp ) /       &
6684                                ( zeta - 1.0_wp ), 0.0_wp                      &
6685                             )   
6686                   lambda = ( pirho_l * nr / lwc *                             &
6687                              ( mu + 3.0_wp ) * ( mu + 2.0_wp ) *              &
6688                              ( mu + 1.0_wp )                                  &
6689                            )**0.3333333_wp
6690                   nr0 =  ( nr / (gamma( mu + 1.0_wp ) ) ) *                   &
6691                          lambda**( mu + 1.0_wp ) 
6692
6693                   DO  n = 0, n_max-1
6694                      diameter         = r_bin_mid(n) * 2.0_wp
6695                      an_spl(n) = nr0 * diameter**mu *                         &
6696                                  EXP( -lambda * diameter ) *                  & 
6697                                  ( r_bin(n+1) - r_bin(n) ) * 2.0_wp 
6698                   ENDDO
6699                ELSEIF ( isf == 2 )  THEN
6700!
6701!--                Lognormal size distribution to calculate critical
6702!--                weight_factor (e.g. Levin, 1971, Bradley + Stow, 1974).
6703                   DO  n = 0, n_max-1
6704                      an_spl(n) = nr / ( SQRT( 2.0_wp * pi ) *                 &
6705                                              LOG(sigma_log) * r_bin_mid(n)    &
6706                                        ) *                                    &
6707                                  EXP( -( LOG( r_bin_mid(n) / rm )**2 ) /      &
6708                                        ( 2.0_wp * LOG(sigma_log)**2 )         &
6709                                      ) *                                      &
6710                                  ( r_bin(n+1) - r_bin(n) )
6711                   ENDDO
6712                ELSEIF ( isf == 3 )  THEN
6713!
6714!--                Exponential size distribution to calculate critical
6715!--                weight_factor (e.g. Berry + Reinhardt, 1974). 
6716                   DO  n = 0, n_max-1
6717                      an_spl(n) = 3.0_wp * nr * r_bin_mid(n)**2 / rm**3 *     &
6718                                  EXP( - ( r_bin_mid(n)**3 / rm**3 ) ) *      &
6719                                  ( r_bin(n+1) - r_bin(n) )
6720                   ENDDO
6721                ENDIF
6722
6723!
6724!--             Criterion to avoid super droplets with a weighting factor < 1.0.
6725                an_spl = MAX(an_spl, 1.0_wp)
6726!
6727!--             Start splitting operations. Each particle is checked if it
6728!--             fulfilled the splitting criterion's. In splitting mode 'gb_av'
6729!--             a critical radius (radius_split) and a splitting function must
6730!--             be prescribed (see particles_par). The critical weighting factor
6731!--             is calculated while appoximating a 'gamma', 'log' or 'exp'-
6732!--             drop size distribution. In this mode a DSD is calculated for
6733!--             every cloudy grid box. Super droplets which have a larger
6734!--             radius and larger weighting factor are split into
6735!--             'splitting_factor' super droplets. In this case the splitting 
6736!--             factor is calculated of weighting factor of the super droplet 
6737!--             and theapproximated number concentration for droplet of such
6738!--             a size. Due to the splitting, the weighting factor of the 
6739!--             super droplet and all created clones is reduced by the factor 
6740!--             of 'splitting_facor'.
6741                DO  n = 1, number_of_particles
6742                   DO  np = 0, n_max-1
6743                      IF ( r_bin(np) >= radius_split  .AND.                    &
6744                           particles(n)%particle_mask  .AND.                   &
6745                           particles(n)%radius >= r_bin(np)    .AND.           &
6746                           particles(n)%radius < r_bin(np+1)   .AND.           &
6747                           particles(n)%weight_factor >= an_spl(np) )          &
6748                      THEN
6749!
6750!--                      Calculate splitting factor.
6751                         splitting_factor =                                    & 
6752                             MIN( INT( particles(n)%weight_factor /            &
6753                                        an_spl(np)                             &
6754                                     ), splitting_factor_max                   &
6755                                )
6756                         IF ( splitting_factor < 2 )  CYCLE
6757
6758!
6759!--                      Calculate the new number of particles.
6760                         new_size = prt_count(k,j,i) + splitting_factor - 1
6761!
6762!--                      Cycle if maximum number of particles per grid box
6763!--                      is greater than the allowed maximum number.
6764                         IF ( new_size >= max_number_particles_per_gridbox )   &
6765                         CYCLE
6766!
6767!--                      Reallocate particle array if necessary.
6768                         IF ( new_size > SIZE(particles) )  THEN
6769                            CALL realloc_particles_array(i,j,k,new_size)
6770                         ENDIF
6771!
6772!--                      Calculate new weighting factor.
6773                         particles(n)%weight_factor = & 
6774                            particles(n)%weight_factor / splitting_factor
6775                         tmp_particle               = particles(n)
6776                         old_size                   = prt_count(k,j,i)
6777!
6778!--                      Create splitting_factor-1 new particles.
6779                         DO jpp = 1, splitting_factor-1
6780                            grid_particles(k,j,i)%particles(jpp+old_size) =    &
6781                               tmp_particle                 
6782                         ENDDO
6783!
6784!--                      Save the new number of droplets for every grid box.
6785                         prt_count(k,j,i)    = prt_count(k,j,i) +              &
6786                                               splitting_factor - 1
6787                         new_particles_gb    = new_particles_gb +              &
6788                                               splitting_factor - 1
6789                      ENDIF
6790                   ENDDO 
6791                ENDDO
6792             ENDDO
6793          ENDDO
6794       ENDDO
6795    ENDIF
6796       
6797    CALL cpu_log( log_point_s(80), 'lpm_splitting', 'stop' )
6798
6799 END SUBROUTINE lpm_splitting
6800 
6801
6802!------------------------------------------------------------------------------!
6803! Description:
6804! ------------
6805! This routine is a part of the Lagrangian particle model. Two Super droplets
6806! which fulfill certain criterion's (e.g. a big weighting factor and a small
6807! radius) can be merged into one super droplet with a increased number of
6808! represented particles of the super droplet. This mechanism ensures an
6809! improved a feasible amount of computational costs. The limits of particle
6810! creation should be chosen carefully! The idea of this algorithm is based on
6811! Unterstrasser and Soelch, 2014.
6812!------------------------------------------------------------------------------!
6813 SUBROUTINE lpm_merging
6814
6815    INTEGER(iwp) ::  i         !<
6816    INTEGER(iwp) ::  j         !<
6817    INTEGER(iwp) ::  k         !<
6818    INTEGER(iwp) ::  n         !<
6819    INTEGER(iwp) ::  merge_drp = 0     !< number of merged droplets
6820
6821
6822    REAL(wp) ::  ql_crit = 1.0E-5_wp  !< threshold lwc for cloudy grid cells
6823                                      !< (e.g. Siebesma et al 2003, JAS, 60)
6824
6825    CALL cpu_log( log_point_s(81), 'lpm_merging', 'start' )
6826
6827    merge_drp  = 0
6828
6829    IF ( weight_factor_merge == -1.0_wp )  THEN
6830       weight_factor_merge = 0.5_wp * initial_weighting_factor 
6831    ENDIF
6832
6833    DO  i = nxl, nxr
6834       DO  j = nys, nyn
6835          DO  k = nzb+1, nzt
6836
6837             number_of_particles = prt_count(k,j,i)
6838             IF ( number_of_particles <= 0  .OR.                               &
6839                   ql(k,j,i) >= ql_crit )  CYCLE
6840             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
6841!
6842!--          Start merging operations: This routine delete super droplets with
6843!--          a small radius (radius <= radius_merge) and a low weighting
6844!--          factor (weight_factor  <= weight_factor_merge). The number of
6845!--          represented particles will be added to the next particle of the
6846!--          particle array. Tests showed that this simplified method can be
6847!--          used because it will only take place outside of cloudy grid
6848!--          boxes where ql <= 1.0E-5 kg/kg. Therefore, especially former cloned
6849!--          and subsequent evaporated super droplets will be merged.
6850             DO  n = 1, number_of_particles-1
6851                IF ( particles(n)%particle_mask                    .AND.       &
6852                     particles(n+1)%particle_mask                  .AND.       &
6853                     particles(n)%radius        <= radius_merge    .AND.       &
6854                     particles(n)%weight_factor <= weight_factor_merge )       &
6855                THEN
6856                   particles(n+1)%weight_factor  =                             &
6857                                       particles(n+1)%weight_factor +          &
6858                                       ( particles(n)%radius**3     /          &
6859                                         particles(n+1)%radius**3   *          &
6860                                         particles(n)%weight_factor            &
6861                                       )
6862                   particles(n)%particle_mask = .FALSE.
6863                   deleted_particles          = deleted_particles + 1 
6864                   merge_drp                  = merge_drp + 1
6865
6866                ENDIF
6867             ENDDO
6868          ENDDO
6869       ENDDO
6870    ENDDO
6871
6872
6873    CALL cpu_log( log_point_s(81), 'lpm_merging', 'stop' )
6874
6875 END SUBROUTINE lpm_merging
6876
6877 
6878
6879 
6880!------------------------------------------------------------------------------!
6881! Description:
6882! ------------
6883!> Exchange between subdomains.
6884!> As soon as one particle has moved beyond the boundary of the domain, it
6885!> is included in the relevant transfer arrays and marked for subsequent
6886!> deletion on this PE.
6887!> First sweep for crossings in x direction. Find out first the number of
6888!> particles to be transferred and allocate temporary arrays needed to store
6889!> them.
6890!> For a one-dimensional decomposition along y, no transfer is necessary,
6891!> because the particle remains on the PE, but the particle coordinate has to
6892!> be adjusted.
6893!------------------------------------------------------------------------------!
6894 SUBROUTINE lpm_exchange_horiz
6895
6896    INTEGER(iwp) ::  i                 !< grid index (x) of particle positition
6897    INTEGER(iwp) ::  ip                !< index variable along x
6898    INTEGER(iwp) ::  j                 !< grid index (y) of particle positition
6899    INTEGER(iwp) ::  jp                !< index variable along y
6900    INTEGER(iwp) ::  kp                !< index variable along z
6901    INTEGER(iwp) ::  n                 !< particle index variable
6902    INTEGER(iwp) ::  par_size          !< Particle size in bytes
6903    INTEGER(iwp) ::  trlp_count        !< number of particles send to left PE
6904    INTEGER(iwp) ::  trlp_count_recv   !< number of particles receive from right PE
6905    INTEGER(iwp) ::  trnp_count        !< number of particles send to north PE
6906    INTEGER(iwp) ::  trnp_count_recv   !< number of particles receive from south PE
6907    INTEGER(iwp) ::  trrp_count        !< number of particles send to right PE
6908    INTEGER(iwp) ::  trrp_count_recv   !< number of particles receive from left PE
6909    INTEGER(iwp) ::  trsp_count        !< number of particles send to south PE
6910    INTEGER(iwp) ::  trsp_count_recv   !< number of particles receive from north PE
6911
6912    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  rvlp  !< particles received from right PE
6913    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  rvnp  !< particles received from south PE
6914    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  rvrp  !< particles received from left PE
6915    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  rvsp  !< particles received from north PE
6916    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  trlp  !< particles send to left PE
6917    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  trnp  !< particles send to north PE
6918    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  trrp  !< particles send to right PE
6919    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  trsp  !< particles send to south PE
6920
6921    CALL cpu_log( log_point_s(23), 'lpm_exchange_horiz', 'start' )
6922
6923#if defined( __parallel )
6924
6925!
6926!-- Exchange between subdomains.
6927!-- As soon as one particle has moved beyond the boundary of the domain, it
6928!-- is included in the relevant transfer arrays and marked for subsequent
6929!-- deletion on this PE.
6930!-- First sweep for crossings in x direction. Find out first the number of
6931!-- particles to be transferred and allocate temporary arrays needed to store
6932!-- them.
6933!-- For a one-dimensional decomposition along y, no transfer is necessary,
6934!-- because the particle remains on the PE, but the particle coordinate has to
6935!-- be adjusted.
6936    trlp_count  = 0
6937    trrp_count  = 0
6938
6939    trlp_count_recv   = 0
6940    trrp_count_recv   = 0
6941
6942    IF ( pdims(1) /= 1 )  THEN
6943!
6944!--    First calculate the storage necessary for sending and receiving the data.
6945!--    Compute only first (nxl) and last (nxr) loop iterration.
6946       DO  ip = nxl, nxr, nxr - nxl
6947          DO  jp = nys, nyn
6948             DO  kp = nzb+1, nzt
6949
6950                number_of_particles = prt_count(kp,jp,ip)
6951                IF ( number_of_particles <= 0 )  CYCLE
6952                particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
6953                DO  n = 1, number_of_particles
6954                   IF ( particles(n)%particle_mask )  THEN
6955                      i = particles(n)%x * ddx
6956!
6957!--                   Above calculation does not work for indices less than zero
6958                      IF ( particles(n)%x < 0.0_wp)  i = -1
6959
6960                      IF ( i < nxl )  THEN
6961                         trlp_count = trlp_count + 1
6962                      ELSEIF ( i > nxr )  THEN
6963                         trrp_count = trrp_count + 1
6964                      ENDIF
6965                   ENDIF
6966                ENDDO
6967
6968             ENDDO
6969          ENDDO
6970       ENDDO
6971
6972       IF ( trlp_count  == 0 )  trlp_count  = 1
6973       IF ( trrp_count  == 0 )  trrp_count  = 1
6974
6975       ALLOCATE( trlp(trlp_count), trrp(trrp_count) )
6976
6977       trlp = zero_particle
6978       trrp = zero_particle
6979
6980       trlp_count  = 0
6981       trrp_count  = 0
6982
6983    ENDIF
6984!
6985!-- Compute only first (nxl) and last (nxr) loop iterration
6986    DO  ip = nxl, nxr, nxr-nxl
6987       DO  jp = nys, nyn
6988          DO  kp = nzb+1, nzt
6989             number_of_particles = prt_count(kp,jp,ip)
6990             IF ( number_of_particles <= 0 ) CYCLE
6991             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
6992             DO  n = 1, number_of_particles
6993!
6994!--             Only those particles that have not been marked as 'deleted' may
6995!--             be moved.
6996                IF ( particles(n)%particle_mask )  THEN
6997
6998                   i = particles(n)%x * ddx
6999!
7000!--                Above calculation does not work for indices less than zero
7001                   IF ( particles(n)%x < 0.0_wp )  i = -1
7002
7003                   IF ( i <  nxl )  THEN
7004                      IF ( i < 0 )  THEN
7005!
7006!--                   Apply boundary condition along x
7007                         IF ( ibc_par_lr == 0 )  THEN
7008!
7009!--                         Cyclic condition
7010                            IF ( pdims(1) == 1 )  THEN
7011                               particles(n)%x        = ( nx + 1 ) * dx + particles(n)%x
7012                               particles(n)%origin_x = ( nx + 1 ) * dx + &
7013                               particles(n)%origin_x
7014                            ELSE
7015                               trlp_count = trlp_count + 1
7016                               trlp(trlp_count)   = particles(n)
7017                               trlp(trlp_count)%x = ( nx + 1 ) * dx + trlp(trlp_count)%x
7018                               trlp(trlp_count)%origin_x = trlp(trlp_count)%origin_x + &
7019                               ( nx + 1 ) * dx
7020                               particles(n)%particle_mask  = .FALSE.
7021                               deleted_particles = deleted_particles + 1
7022
7023                               IF ( trlp(trlp_count)%x >= (nx + 1)* dx - 1.0E-12_wp )  THEN
7024                                  trlp(trlp_count)%x = trlp(trlp_count)%x - 1.0E-10_wp
7025                                  !++ why is 1 subtracted in next statement???
7026                                  trlp(trlp_count)%origin_x = trlp(trlp_count)%origin_x - 1
7027                               ENDIF
7028
7029                            ENDIF
7030
7031                         ELSEIF ( ibc_par_lr == 1 )  THEN
7032!
7033!--                         Particle absorption
7034                            particles(n)%particle_mask = .FALSE.
7035                            deleted_particles = deleted_particles + 1
7036
7037                         ELSEIF ( ibc_par_lr == 2 )  THEN
7038!
7039!--                         Particle reflection
7040                            particles(n)%x       = -particles(n)%x
7041                            particles(n)%speed_x = -particles(n)%speed_x
7042
7043                         ENDIF
7044                      ELSE
7045!
7046!--                      Store particle data in the transfer array, which will be
7047!--                      send to the neighbouring PE
7048                         trlp_count = trlp_count + 1
7049                         trlp(trlp_count) = particles(n)
7050                         particles(n)%particle_mask = .FALSE.
7051                         deleted_particles = deleted_particles + 1
7052
7053                      ENDIF
7054
7055                   ELSEIF ( i > nxr )  THEN
7056                      IF ( i > nx )  THEN
7057!
7058!--                      Apply boundary condition along x
7059                         IF ( ibc_par_lr == 0 )  THEN
7060!
7061!--                         Cyclic condition
7062                            IF ( pdims(1) == 1 )  THEN
7063                               particles(n)%x = particles(n)%x - ( nx + 1 ) * dx
7064                               particles(n)%origin_x = particles(n)%origin_x - &
7065                               ( nx + 1 ) * dx
7066                            ELSE
7067                               trrp_count = trrp_count + 1
7068                               trrp(trrp_count) = particles(n)
7069                               trrp(trrp_count)%x = trrp(trrp_count)%x - ( nx + 1 ) * dx
7070                               trrp(trrp_count)%origin_x = trrp(trrp_count)%origin_x - &
7071                               ( nx + 1 ) * dx
7072                               particles(n)%particle_mask = .FALSE.
7073                               deleted_particles = deleted_particles + 1
7074
7075                            ENDIF
7076
7077                         ELSEIF ( ibc_par_lr == 1 )  THEN
7078!
7079!--                         Particle absorption
7080                            particles(n)%particle_mask = .FALSE.
7081                            deleted_particles = deleted_particles + 1
7082
7083                         ELSEIF ( ibc_par_lr == 2 )  THEN
7084!
7085!--                         Particle reflection
7086                            particles(n)%x       = 2 * ( nx * dx ) - particles(n)%x
7087                            particles(n)%speed_x = -particles(n)%speed_x
7088
7089                         ENDIF
7090                      ELSE
7091!
7092!--                      Store particle data in the transfer array, which will be send
7093!--                      to the neighbouring PE
7094                         trrp_count = trrp_count + 1
7095                         trrp(trrp_count) = particles(n)
7096                         particles(n)%particle_mask = .FALSE.
7097                         deleted_particles = deleted_particles + 1
7098
7099                      ENDIF
7100
7101                   ENDIF
7102                ENDIF
7103
7104             ENDDO
7105          ENDDO
7106       ENDDO
7107    ENDDO
7108
7109!
7110!-- STORAGE_SIZE returns the storage size of argument A in bits. However , it
7111!-- is needed in bytes. The function C_SIZEOF which produces this value directly
7112!-- causes problems with gfortran. For this reason the use of C_SIZEOF is avoided
7113    par_size = STORAGE_SIZE(trlp(1))/8
7114
7115
7116!
7117!-- Allocate arrays required for north-south exchange, as these
7118!-- are used directly after particles are exchange along x-direction.
7119    ALLOCATE( move_also_north(1:NR_2_direction_move) )
7120    ALLOCATE( move_also_south(1:NR_2_direction_move) )
7121
7122    nr_move_north = 0
7123    nr_move_south = 0
7124!
7125!-- Send left boundary, receive right boundary (but first exchange how many
7126!-- and check, if particle storage must be extended)
7127    IF ( pdims(1) /= 1 )  THEN
7128
7129       CALL MPI_SENDRECV( trlp_count,      1, MPI_INTEGER, pleft,  0, &
7130                          trrp_count_recv, 1, MPI_INTEGER, pright, 0, &
7131                          comm2d, status, ierr )
7132
7133       ALLOCATE(rvrp(MAX(1,trrp_count_recv)))
7134
7135       CALL MPI_SENDRECV( trlp, max(1,trlp_count)*par_size, MPI_BYTE,&
7136                          pleft, 1, rvrp,                            &
7137                          max(1,trrp_count_recv)*par_size, MPI_BYTE, pright, 1,&
7138                          comm2d, status, ierr )
7139
7140       IF ( trrp_count_recv > 0 )  CALL lpm_add_particles_to_gridcell(rvrp(1:trrp_count_recv))
7141
7142       DEALLOCATE(rvrp)
7143
7144!
7145!--    Send right boundary, receive left boundary
7146       CALL MPI_SENDRECV( trrp_count,      1, MPI_INTEGER, pright, 0, &
7147                          trlp_count_recv, 1, MPI_INTEGER, pleft,  0, &
7148                          comm2d, status, ierr )
7149
7150       ALLOCATE(rvlp(MAX(1,trlp_count_recv)))
7151!
7152!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
7153!--    variables in structure particle_type (due to the calculation of par_size)
7154       CALL MPI_SENDRECV( trrp, max(1,trrp_count)*par_size, MPI_BYTE,&
7155                          pright, 1, rvlp,                           &
7156                          max(1,trlp_count_recv)*par_size, MPI_BYTE, pleft, 1, &
7157                          comm2d, status, ierr )
7158
7159       IF ( trlp_count_recv > 0 )  CALL lpm_add_particles_to_gridcell(rvlp(1:trlp_count_recv))
7160
7161       DEALLOCATE( rvlp )
7162       DEALLOCATE( trlp, trrp )
7163
7164    ENDIF
7165
7166!
7167!-- Check whether particles have crossed the boundaries in y direction. Note
7168!-- that this case can also apply to particles that have just been received
7169!-- from the adjacent right or left PE.
7170!-- Find out first the number of particles to be transferred and allocate
7171!-- temporary arrays needed to store them.
7172!-- For a one-dimensional decomposition along y, no transfer is necessary,
7173!-- because the particle remains on the PE.
7174    trsp_count  = nr_move_south
7175    trnp_count  = nr_move_north
7176
7177    trsp_count_recv   = 0
7178    trnp_count_recv   = 0
7179
7180    IF ( pdims(2) /= 1 )  THEN
7181!
7182!--    First calculate the storage necessary for sending and receiving the
7183!--    data
7184       DO  ip = nxl, nxr
7185          DO  jp = nys, nyn, nyn-nys    !compute only first (nys) and last (nyn) loop iterration
7186             DO  kp = nzb+1, nzt
7187                number_of_particles = prt_count(kp,jp,ip)
7188                IF ( number_of_particles <= 0 )  CYCLE
7189                particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
7190                DO  n = 1, number_of_particles
7191                   IF ( particles(n)%particle_mask )  THEN
7192                      j = particles(n)%y * ddy
7193!
7194!--                   Above calculation does not work for indices less than zero
7195                      IF ( particles(n)%y < 0.0_wp)  j = -1
7196
7197                      IF ( j < nys )  THEN
7198                         trsp_count = trsp_count + 1
7199                      ELSEIF ( j > nyn )  THEN
7200                         trnp_count = trnp_count + 1
7201                      ENDIF
7202                   ENDIF
7203                ENDDO
7204             ENDDO
7205          ENDDO
7206       ENDDO
7207
7208       IF ( trsp_count  == 0 )  trsp_count  = 1
7209       IF ( trnp_count  == 0 )  trnp_count  = 1
7210
7211       ALLOCATE( trsp(trsp_count), trnp(trnp_count) )
7212
7213       trsp = zero_particle
7214       trnp = zero_particle
7215
7216       trsp_count  = nr_move_south
7217       trnp_count  = nr_move_north
7218
7219       trsp(1:nr_move_south) = move_also_south(1:nr_move_south)
7220       trnp(1:nr_move_north) = move_also_north(1:nr_move_north)
7221
7222    ENDIF
7223
7224    DO  ip = nxl, nxr
7225       DO  jp = nys, nyn, nyn-nys ! compute only first (nys) and last (nyn) loop iterration
7226          DO  kp = nzb+1, nzt
7227             number_of_particles = prt_count(kp,jp,ip)
7228             IF ( number_of_particles <= 0 )  CYCLE
7229             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
7230             DO  n = 1, number_of_particles
7231!
7232!--             Only those particles that have not been marked as 'deleted' may
7233!--             be moved.
7234                IF ( particles(n)%particle_mask )  THEN
7235
7236                   j = particles(n)%y * ddy
7237!
7238!--                Above calculation does not work for indices less than zero
7239                   IF ( particles(n)%y < 0.0_wp )  j = -1
7240
7241                   IF ( j < nys )  THEN
7242                      IF ( j < 0 )  THEN
7243!
7244!--                      Apply boundary condition along y
7245                         IF ( ibc_par_ns == 0 )  THEN
7246!
7247!--                         Cyclic condition
7248                            IF ( pdims(2) == 1 )  THEN
7249                               particles(n)%y = ( ny + 1 ) * dy + particles(n)%y
7250                               particles(n)%origin_y = ( ny + 1 ) * dy + &
7251                                                     particles(n)%origin_y
7252                            ELSE
7253                               trsp_count         = trsp_count + 1
7254                               trsp(trsp_count)   = particles(n)
7255                               trsp(trsp_count)%y = ( ny + 1 ) * dy + &
7256                                                 trsp(trsp_count)%y
7257                               trsp(trsp_count)%origin_y = trsp(trsp_count)%origin_y &
7258                                                + ( ny + 1 ) * dy
7259                               particles(n)%particle_mask = .FALSE.
7260                               deleted_particles = deleted_particles + 1
7261
7262                               IF ( trsp(trsp_count)%y >= (ny+1)* dy - 1.0E-12_wp )  THEN
7263                                  trsp(trsp_count)%y = trsp(trsp_count)%y - 1.0E-10_wp
7264                                  !++ why is 1 subtracted in next statement???
7265                                  trsp(trsp_count)%origin_y =                        &
7266                                                  trsp(trsp_count)%origin_y - 1
7267                               ENDIF
7268
7269                            ENDIF
7270
7271                         ELSEIF ( ibc_par_ns == 1 )  THEN
7272!
7273!--                         Particle absorption
7274                            particles(n)%particle_mask = .FALSE.
7275                            deleted_particles          = deleted_particles + 1
7276
7277                         ELSEIF ( ibc_par_ns == 2 )  THEN
7278!
7279!--                         Particle reflection
7280                            particles(n)%y       = -particles(n)%y
7281                            particles(n)%speed_y = -particles(n)%speed_y
7282
7283                         ENDIF
7284                      ELSE
7285!
7286!--                      Store particle data in the transfer array, which will
7287!--                      be send to the neighbouring PE
7288                         trsp_count = trsp_count + 1
7289                         trsp(trsp_count) = particles(n)
7290                         particles(n)%particle_mask = .FALSE.
7291                         deleted_particles = deleted_particles + 1
7292
7293                      ENDIF
7294
7295                   ELSEIF ( j > nyn )  THEN
7296                      IF ( j > ny )  THEN
7297!
7298!--                       Apply boundary condition along y
7299                         IF ( ibc_par_ns == 0 )  THEN
7300!
7301!--                         Cyclic condition
7302                            IF ( pdims(2) == 1 )  THEN
7303                               particles(n)%y        = particles(n)%y - ( ny + 1 ) * dy
7304                               particles(n)%origin_y =                         &
7305                                          particles(n)%origin_y - ( ny + 1 ) * dy
7306                            ELSE
7307                               trnp_count         = trnp_count + 1
7308                               trnp(trnp_count)   = particles(n)
7309                               trnp(trnp_count)%y =                            &
7310                                          trnp(trnp_count)%y - ( ny + 1 ) * dy
7311                               trnp(trnp_count)%origin_y =                     &
7312                                         trnp(trnp_count)%origin_y - ( ny + 1 ) * dy
7313                               particles(n)%particle_mask = .FALSE.
7314                               deleted_particles          = deleted_particles + 1
7315                            ENDIF
7316
7317                         ELSEIF ( ibc_par_ns == 1 )  THEN
7318!
7319!--                         Particle absorption
7320                            particles(n)%particle_mask = .FALSE.
7321                            deleted_particles = deleted_particles + 1
7322
7323                         ELSEIF ( ibc_par_ns == 2 )  THEN
7324!
7325!--                         Particle reflection
7326                            particles(n)%y       = 2 * ( ny * dy ) - particles(n)%y
7327                            particles(n)%speed_y = -particles(n)%speed_y
7328
7329                         ENDIF
7330                      ELSE
7331!
7332!--                      Store particle data in the transfer array, which will
7333!--                      be send to the neighbouring PE
7334                         trnp_count = trnp_count + 1
7335                         trnp(trnp_count) = particles(n)
7336                         particles(n)%particle_mask = .FALSE.
7337                         deleted_particles = deleted_particles + 1
7338
7339                      ENDIF
7340
7341                   ENDIF
7342                ENDIF
7343             ENDDO
7344          ENDDO
7345       ENDDO
7346    ENDDO
7347
7348!
7349!-- Send front boundary, receive back boundary (but first exchange how many
7350!-- and check, if particle storage must be extended)
7351    IF ( pdims(2) /= 1 )  THEN
7352
7353       CALL MPI_SENDRECV( trsp_count,      1, MPI_INTEGER, psouth, 0, &
7354                          trnp_count_recv, 1, MPI_INTEGER, pnorth, 0, &
7355                          comm2d, status, ierr )
7356
7357       ALLOCATE(rvnp(MAX(1,trnp_count_recv)))
7358!
7359!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
7360!--    variables in structure particle_type (due to the calculation of par_size)
7361       CALL MPI_SENDRECV( trsp, trsp_count*par_size, MPI_BYTE,      &
7362                          psouth, 1, rvnp,                             &
7363                          trnp_count_recv*par_size, MPI_BYTE, pnorth, 1,   &
7364                          comm2d, status, ierr )
7365
7366       IF ( trnp_count_recv  > 0 )  CALL lpm_add_particles_to_gridcell(rvnp(1:trnp_count_recv))
7367
7368       DEALLOCATE(rvnp)
7369
7370!
7371!--    Send back boundary, receive front boundary
7372       CALL MPI_SENDRECV( trnp_count,      1, MPI_INTEGER, pnorth, 0, &
7373                          trsp_count_recv, 1, MPI_INTEGER, psouth, 0, &
7374                          comm2d, status, ierr )
7375
7376       ALLOCATE(rvsp(MAX(1,trsp_count_recv)))
7377!
7378!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
7379!--    variables in structure particle_type (due to the calculation of par_size)
7380       CALL MPI_SENDRECV( trnp, trnp_count*par_size, MPI_BYTE,      &
7381                          pnorth, 1, rvsp,                          &
7382                          trsp_count_recv*par_size, MPI_BYTE, psouth, 1,   &
7383                          comm2d, status, ierr )
7384
7385       IF ( trsp_count_recv > 0 )  CALL lpm_add_particles_to_gridcell(rvsp(1:trsp_count_recv))
7386
7387       DEALLOCATE(rvsp)
7388
7389       number_of_particles = number_of_particles + trsp_count_recv
7390
7391       DEALLOCATE( trsp, trnp )
7392
7393    ENDIF
7394
7395    DEALLOCATE( move_also_north )
7396    DEALLOCATE( move_also_south )
7397
7398#else
7399
7400    DO  ip = nxl, nxr, nxr-nxl
7401       DO  jp = nys, nyn
7402          DO  kp = nzb+1, nzt
7403             number_of_particles = prt_count(kp,jp,ip)
7404             IF ( number_of_particles <= 0 )  CYCLE
7405             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
7406             DO  n = 1, number_of_particles
7407!
7408!--             Apply boundary conditions
7409
7410                IF ( particles(n)%x < 0.0_wp )  THEN
7411
7412                   IF ( ibc_par_lr == 0 )  THEN
7413!
7414!--                   Cyclic boundary. Relevant coordinate has to be changed.
7415                      particles(n)%x = ( nx + 1 ) * dx + particles(n)%x
7416                      particles(n)%origin_x = ( nx + 1 ) * dx + &
7417                               particles(n)%origin_x
7418                   ELSEIF ( ibc_par_lr == 1 )  THEN
7419!
7420!--                   Particle absorption
7421                      particles(n)%particle_mask = .FALSE.
7422                      deleted_particles = deleted_particles + 1
7423
7424                   ELSEIF ( ibc_par_lr == 2 )  THEN
7425!
7426!--                   Particle reflection
7427                      particles(n)%x       = -dx - particles(n)%x
7428                      particles(n)%speed_x = -particles(n)%speed_x
7429                   ENDIF
7430
7431                ELSEIF ( particles(n)%x >= ( nx + 1) * dx )  THEN
7432
7433                   IF ( ibc_par_lr == 0 )  THEN
7434!
7435!--                   Cyclic boundary. Relevant coordinate has to be changed.
7436                      particles(n)%x = particles(n)%x - ( nx + 1 ) * dx
7437                      particles(n)%origin_x = particles(n)%origin_x - &
7438                               ( nx + 1 ) * dx
7439
7440                   ELSEIF ( ibc_par_lr == 1 )  THEN
7441!
7442!--                   Particle absorption
7443                      particles(n)%particle_mask = .FALSE.
7444                      deleted_particles = deleted_particles + 1
7445
7446                   ELSEIF ( ibc_par_lr == 2 )  THEN
7447!
7448!--                   Particle reflection
7449                      particles(n)%x       = ( nx + 1 ) * dx - particles(n)%x
7450                      particles(n)%speed_x = -particles(n)%speed_x
7451                   ENDIF
7452
7453                ENDIF
7454             ENDDO
7455          ENDDO
7456       ENDDO
7457    ENDDO
7458
7459    DO  ip = nxl, nxr
7460       DO  jp = nys, nyn, nyn-nys
7461          DO  kp = nzb+1, nzt
7462             number_of_particles = prt_count(kp,jp,ip)
7463             IF ( number_of_particles <= 0 )  CYCLE
7464             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
7465             DO  n = 1, number_of_particles
7466
7467                IF ( particles(n)%y < 0.0_wp)  THEN
7468
7469                   IF ( ibc_par_ns == 0 )  THEN
7470!
7471!--                   Cyclic boundary. Relevant coordinate has to be changed.
7472                      particles(n)%y = ( ny + 1 ) * dy + particles(n)%y
7473                      particles(n)%origin_y = ( ny + 1 ) * dy + &
7474                           particles(n)%origin_y
7475
7476                   ELSEIF ( ibc_par_ns == 1 )  THEN
7477!
7478!--                   Particle absorption
7479                      particles(n)%particle_mask = .FALSE.
7480                      deleted_particles = deleted_particles + 1
7481
7482                   ELSEIF ( ibc_par_ns == 2 )  THEN
7483!
7484!--                   Particle reflection
7485                      particles(n)%y       = -dy - particles(n)%y
7486                      particles(n)%speed_y = -particles(n)%speed_y
7487                   ENDIF
7488
7489                ELSEIF ( particles(n)%y >= ( ny + 1) * dy )  THEN
7490
7491                   IF ( ibc_par_ns == 0 )  THEN
7492!
7493!--                   Cyclic boundary. Relevant coordinate has to be changed.
7494                      particles(n)%y = particles(n)%y - ( ny + 1 ) * dy
7495                      particles(n)%origin_y = particles(n)%origin_y - &
7496                                ( ny + 1 ) * dy
7497
7498                   ELSEIF ( ibc_par_ns == 1 )  THEN
7499!
7500!--                   Particle absorption
7501                      particles(n)%particle_mask = .FALSE.
7502                      deleted_particles = deleted_particles + 1
7503
7504                   ELSEIF ( ibc_par_ns == 2 )  THEN
7505!
7506!--                   Particle reflection
7507                      particles(n)%y       = ( ny + 1 ) * dy - particles(n)%y
7508                      particles(n)%speed_y = -particles(n)%speed_y
7509                   ENDIF
7510
7511                ENDIF
7512
7513             ENDDO
7514          ENDDO
7515       ENDDO
7516    ENDDO
7517#endif
7518
7519!
7520!-- Accumulate the number of particles transferred between the subdomains
7521#if defined( __parallel )
7522    trlp_count_sum      = trlp_count_sum      + trlp_count
7523    trlp_count_recv_sum = trlp_count_recv_sum + trlp_count_recv
7524    trrp_count_sum      = trrp_count_sum      + trrp_count
7525    trrp_count_recv_sum = trrp_count_recv_sum + trrp_count_recv
7526    trsp_count_sum      = trsp_count_sum      + trsp_count
7527    trsp_count_recv_sum = trsp_count_recv_sum + trsp_count_recv
7528    trnp_count_sum      = trnp_count_sum      + trnp_count
7529    trnp_count_recv_sum = trnp_count_recv_sum + trnp_count_recv
7530#endif
7531
7532    CALL cpu_log( log_point_s(23), 'lpm_exchange_horiz', 'stop' )
7533
7534 END SUBROUTINE lpm_exchange_horiz
7535
7536!------------------------------------------------------------------------------!
7537! Description:
7538! ------------
7539!> If a particle moves from one processor to another, this subroutine moves
7540!> the corresponding elements from the particle arrays of the old grid cells
7541!> to the particle arrays of the new grid cells.
7542!------------------------------------------------------------------------------!
7543 SUBROUTINE lpm_add_particles_to_gridcell (particle_array)
7544
7545    IMPLICIT NONE
7546
7547    INTEGER(iwp)        ::  ip        !< grid index (x) of particle
7548    INTEGER(iwp)        ::  jp        !< grid index (x) of particle
7549    INTEGER(iwp)        ::  kp        !< grid index (x) of particle
7550    INTEGER(iwp)        ::  n         !< index variable of particle
7551    INTEGER(iwp)        ::  pindex    !< dummy argument for new number of particles per grid box
7552
7553    LOGICAL             ::  pack_done !<
7554
7555    TYPE(particle_type), DIMENSION(:), INTENT(IN)  ::  particle_array !< new particles in a grid box
7556    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  temp_ns        !< temporary particle array for reallocation
7557
7558    pack_done     = .FALSE.
7559
7560    DO n = 1, SIZE(particle_array)
7561
7562       IF ( .NOT. particle_array(n)%particle_mask )  CYCLE
7563
7564       ip = particle_array(n)%x * ddx
7565       jp = particle_array(n)%y * ddy
7566!
7567!--    In case of stretching the actual k index must be found
7568       IF ( dz_stretch_level .NE. -9999999.9_wp  .OR.         &
7569            dz_stretch_level_start(1) .NE. -9999999.9_wp ) THEN
7570          kp = MINLOC( ABS( particle_array(n)%z - zu ), DIM = 1 ) - 1
7571       ELSE
7572          kp = INT( particle_array(n)%z / dz(1) + 1 + offset_ocean_nzt )
7573       ENDIF
7574
7575       IF ( ip >= nxl  .AND.  ip <= nxr  .AND.  jp >= nys  .AND.  jp <= nyn    &
7576            .AND.  kp >= nzb+1  .AND.  kp <= nzt)  THEN ! particle stays on processor
7577          number_of_particles = prt_count(kp,jp,ip)
7578          particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
7579
7580          pindex = prt_count(kp,jp,ip)+1
7581          IF( pindex > SIZE(grid_particles(kp,jp,ip)%particles) )  THEN
7582             IF ( pack_done )  THEN
7583                CALL realloc_particles_array (ip,jp,kp)
7584             ELSE
7585                CALL lpm_pack
7586                prt_count(kp,jp,ip) = number_of_particles
7587                pindex = prt_count(kp,jp,ip)+1
7588                IF ( pindex > SIZE(grid_particles(kp,jp,ip)%particles) )  THEN
7589                   CALL realloc_particles_array (ip,jp,kp)
7590                ENDIF
7591                pack_done = .TRUE.
7592             ENDIF
7593          ENDIF
7594          grid_particles(kp,jp,ip)%particles(pindex) = particle_array(n)
7595          prt_count(kp,jp,ip) = pindex
7596       ELSE
7597          IF ( jp <= nys - 1 )  THEN
7598             nr_move_south = nr_move_south+1
7599!
7600!--          Before particle information is swapped to exchange-array, check
7601!--          if enough memory is allocated. If required, reallocate exchange
7602!--          array.
7603             IF ( nr_move_south > SIZE(move_also_south) )  THEN
7604!
7605!--             At first, allocate further temporary array to swap particle
7606!--             information.
7607                ALLOCATE( temp_ns(SIZE(move_also_south)+NR_2_direction_move) )
7608                temp_ns(1:nr_move_south-1) = move_also_south(1:nr_move_south-1)
7609                DEALLOCATE( move_also_south )
7610                ALLOCATE( move_also_south(SIZE(temp_ns)) )
7611                move_also_south(1:nr_move_south-1) = temp_ns(1:nr_move_south-1)
7612                DEALLOCATE( temp_ns )
7613
7614             ENDIF
7615
7616             move_also_south(nr_move_south) = particle_array(n)
7617
7618             IF ( jp == -1 )  THEN
7619!
7620!--             Apply boundary condition along y
7621                IF ( ibc_par_ns == 0 )  THEN
7622                   move_also_south(nr_move_south)%y =                          &
7623                      move_also_south(nr_move_south)%y + ( ny + 1 ) * dy
7624                   move_also_south(nr_move_south)%origin_y =                   &
7625                      move_also_south(nr_move_south)%origin_y + ( ny + 1 ) * dy
7626                ELSEIF ( ibc_par_ns == 1 )  THEN
7627!
7628!--                Particle absorption
7629                   move_also_south(nr_move_south)%particle_mask = .FALSE.
7630                   deleted_particles = deleted_particles + 1
7631
7632                ELSEIF ( ibc_par_ns == 2 )  THEN
7633!
7634!--                Particle reflection
7635                   move_also_south(nr_move_south)%y       =                    &
7636                      -move_also_south(nr_move_south)%y
7637                   move_also_south(nr_move_south)%speed_y =                    &
7638                      -move_also_south(nr_move_south)%speed_y
7639
7640                ENDIF
7641             ENDIF
7642          ELSEIF ( jp >= nyn+1 )  THEN
7643             nr_move_north = nr_move_north+1
7644!
7645!--          Before particle information is swapped to exchange-array, check
7646!--          if enough memory is allocated. If required, reallocate exchange
7647!--          array.
7648             IF ( nr_move_north > SIZE(move_also_north) )  THEN
7649!
7650!--             At first, allocate further temporary array to swap particle
7651!--             information.
7652                ALLOCATE( temp_ns(SIZE(move_also_north)+NR_2_direction_move) )
7653                temp_ns(1:nr_move_north-1) = move_also_south(1:nr_move_north-1)
7654                DEALLOCATE( move_also_north )
7655                ALLOCATE( move_also_north(SIZE(temp_ns)) )
7656                move_also_north(1:nr_move_north-1) = temp_ns(1:nr_move_north-1)
7657                DEALLOCATE( temp_ns )
7658
7659             ENDIF
7660
7661             move_also_north(nr_move_north) = particle_array(n)
7662             IF ( jp == ny+1 )  THEN
7663!
7664!--             Apply boundary condition along y
7665                IF ( ibc_par_ns == 0 )  THEN
7666
7667                   move_also_north(nr_move_north)%y =                          &
7668                      move_also_north(nr_move_north)%y - ( ny + 1 ) * dy
7669                   move_also_north(nr_move_north)%origin_y =                   &
7670                      move_also_north(nr_move_north)%origin_y - ( ny + 1 ) * dy
7671                ELSEIF ( ibc_par_ns == 1 )  THEN
7672!
7673!--                Particle absorption
7674                   move_also_north(nr_move_north)%particle_mask = .FALSE.
7675                   deleted_particles = deleted_particles + 1
7676
7677                ELSEIF ( ibc_par_ns == 2 )  THEN
7678!
7679!--                Particle reflection
7680                   move_also_north(nr_move_north)%y       =                    &
7681                      -move_also_north(nr_move_north)%y
7682                   move_also_north(nr_move_north)%speed_y =                    &
7683                      -move_also_north(nr_move_north)%speed_y
7684
7685                ENDIF
7686             ENDIF
7687          ELSE
7688             WRITE(0,'(a,8i7)') 'particle out of range ',myid,ip,jp,kp,nxl,nxr,nys,nyn
7689          ENDIF
7690       ENDIF
7691    ENDDO
7692
7693    RETURN
7694
7695 END SUBROUTINE lpm_add_particles_to_gridcell
7696 
7697 
7698!------------------------------------------------------------------------------!
7699! Description:
7700! ------------
7701!> If a particle moves from one grid cell to another (on the current
7702!> processor!), this subroutine moves the corresponding element from the
7703!> particle array of the old grid cell to the particle array of the new grid
7704!> cell.
7705!------------------------------------------------------------------------------!
7706 SUBROUTINE lpm_move_particle
7707 
7708    INTEGER(iwp)        ::  i           !< grid index (x) of particle position
7709    INTEGER(iwp)        ::  ip          !< index variable along x
7710    INTEGER(iwp)        ::  j           !< grid index (y) of particle position
7711    INTEGER(iwp)        ::  jp          !< index variable along y
7712    INTEGER(iwp)        ::  k           !< grid index (z) of particle position
7713    INTEGER(iwp)        ::  kp          !< index variable along z
7714    INTEGER(iwp)        ::  n           !< index variable for particle array
7715    INTEGER(iwp)        ::  np_before_move !< number of particles per grid box before moving
7716    INTEGER(iwp)        ::  pindex      !< dummy argument for number of new particle per grid box
7717
7718    TYPE(particle_type), DIMENSION(:), POINTER  ::  particles_before_move !< particles before moving
7719
7720    CALL cpu_log( log_point_s(41), 'lpm_move_particle', 'start' )
7721    CALL lpm_check_cfl
7722    DO  ip = nxl, nxr
7723       DO  jp = nys, nyn
7724          DO  kp = nzb+1, nzt
7725
7726             np_before_move = prt_count(kp,jp,ip)
7727             IF ( np_before_move <= 0 )  CYCLE
7728             particles_before_move => grid_particles(kp,jp,ip)%particles(1:np_before_move)
7729
7730             DO  n = 1, np_before_move
7731                i = particles_before_move(n)%x * ddx
7732                j = particles_before_move(n)%y * ddy
7733                k = kp
7734!
7735!--             Find correct vertical particle grid box (necessary in case of grid stretching)
7736!--             Due to the CFL limitations only the neighbouring grid boxes are considered.
7737                IF( zw(k)   < particles_before_move(n)%z ) k = k + 1
7738                IF( zw(k-1) > particles_before_move(n)%z ) k = k - 1 
7739
7740!--             For lpm_exchange_horiz to work properly particles need to be moved to the outermost gridboxes
7741!--             of the respective processor. If the particle index is inside the processor the following lines
7742!--             will not change the index
7743                i = MIN ( i , nxr )
7744                i = MAX ( i , nxl )
7745                j = MIN ( j , nyn )
7746                j = MAX ( j , nys )
7747
7748                k = MIN ( k , nzt )
7749                k = MAX ( k , nzb+1 )
7750
7751!
7752!--             Check, if particle has moved to another grid cell.
7753                IF ( i /= ip  .OR.  j /= jp  .OR.  k /= kp )  THEN
7754!!
7755!--                If the particle stays on the same processor, the particle
7756!--                will be added to the particle array of the new processor.
7757                   number_of_particles = prt_count(k,j,i)
7758                   particles => grid_particles(k,j,i)%particles(1:number_of_particles)
7759
7760                   pindex = prt_count(k,j,i)+1
7761                   IF (  pindex > SIZE(grid_particles(k,j,i)%particles)  )     &
7762                   THEN
7763                      CALL realloc_particles_array(i,j,k)
7764                   ENDIF
7765
7766                   grid_particles(k,j,i)%particles(pindex) = particles_before_move(n)
7767                   prt_count(k,j,i) = pindex
7768
7769                   particles_before_move(n)%particle_mask = .FALSE.
7770                ENDIF
7771             ENDDO
7772
7773          ENDDO
7774       ENDDO
7775    ENDDO
7776
7777    CALL cpu_log( log_point_s(41), 'lpm_move_particle', 'stop' )
7778
7779    RETURN
7780
7781 END SUBROUTINE lpm_move_particle
7782 
7783
7784!------------------------------------------------------------------------------!
7785! Description:
7786! ------------
7787!> Check CFL-criterion for each particle. If one particle violated the
7788!> criterion the particle will be deleted and a warning message is given.
7789!------------------------------------------------------------------------------!
7790 SUBROUTINE lpm_check_cfl 
7791
7792    IMPLICIT NONE
7793
7794    INTEGER(iwp)  ::  i !< running index, x-direction
7795    INTEGER(iwp)  ::  j !< running index, y-direction
7796    INTEGER(iwp)  ::  k !< running index, z-direction
7797    INTEGER(iwp)  ::  n !< running index, number of particles
7798
7799    DO  i = nxl, nxr
7800       DO  j = nys, nyn
7801          DO  k = nzb+1, nzt
7802             number_of_particles = prt_count(k,j,i)
7803             IF ( number_of_particles <= 0 )  CYCLE
7804             particles => grid_particles(k,j,i)%particles(1:number_of_particles)         
7805             DO n = 1, number_of_particles
7806!
7807!--             Note, check for CFL does not work at first particle timestep
7808!--             when both, age and age_m are zero.
7809                IF ( particles(n)%age - particles(n)%age_m > 0.0_wp )  THEN 
7810                   IF(ABS(particles(n)%speed_x) >                              &
7811                      (dx/(particles(n)%age-particles(n)%age_m))  .OR.         &
7812                      ABS(particles(n)%speed_y) >                              & 
7813                      (dy/(particles(n)%age-particles(n)%age_m))  .OR.         &
7814                      ABS(particles(n)%speed_z) >                              &
7815                      ((zw(k)-zw(k-1))/(particles(n)%age-particles(n)%age_m))) &
7816                   THEN
7817                      WRITE( message_string, * )                               &
7818                      'Particle violated CFL-criterion: &particle with id ',   &
7819                      particles(n)%id, ' will be deleted!'   
7820                      CALL message( 'lpm_check_cfl', 'PA0475', 0, 1, -1, 6, 0 )
7821                      particles(n)%particle_mask= .FALSE.
7822                   ENDIF
7823                ENDIF
7824             ENDDO
7825          ENDDO
7826       ENDDO
7827    ENDDO   
7828
7829 END SUBROUTINE lpm_check_cfl
7830 
7831 
7832!------------------------------------------------------------------------------!
7833! Description:
7834! ------------
7835!> If the allocated memory for the particle array do not suffice to add arriving
7836!> particles from neighbour grid cells, this subrouting reallocates the
7837!> particle array to assure enough memory is available.
7838!------------------------------------------------------------------------------!
7839 SUBROUTINE realloc_particles_array ( i, j, k, size_in )
7840
7841    INTEGER(iwp), INTENT(IN)                       ::  i              !<
7842    INTEGER(iwp), INTENT(IN)                       ::  j              !<
7843    INTEGER(iwp), INTENT(IN)                       ::  k              !<
7844    INTEGER(iwp), INTENT(IN), OPTIONAL             ::  size_in        !<
7845
7846    INTEGER(iwp)                                   ::  old_size        !<
7847    INTEGER(iwp)                                   ::  new_size        !<
7848    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  tmp_particles_d !<
7849    TYPE(particle_type), DIMENSION(500)            ::  tmp_particles_s !<
7850
7851    old_size = SIZE(grid_particles(k,j,i)%particles)
7852
7853    IF ( PRESENT(size_in) )   THEN
7854       new_size = size_in
7855    ELSE
7856       new_size = old_size * ( 1.0_wp + alloc_factor / 100.0_wp )
7857    ENDIF
7858
7859    new_size = MAX( new_size, 1, old_size + 1 )
7860
7861    IF ( old_size <= 500 )  THEN
7862
7863       tmp_particles_s(1:old_size) = grid_particles(k,j,i)%particles(1:old_size)
7864
7865       DEALLOCATE(grid_particles(k,j,i)%particles)
7866       ALLOCATE(grid_particles(k,j,i)%particles(new_size))
7867
7868       grid_particles(k,j,i)%particles(1:old_size)          = tmp_particles_s(1:old_size)
7869       grid_particles(k,j,i)%particles(old_size+1:new_size) = zero_particle
7870
7871    ELSE
7872
7873       ALLOCATE(tmp_particles_d(new_size))
7874       tmp_particles_d(1:old_size) = grid_particles(k,j,i)%particles
7875
7876       DEALLOCATE(grid_particles(k,j,i)%particles)
7877       ALLOCATE(grid_particles(k,j,i)%particles(new_size))
7878
7879       grid_particles(k,j,i)%particles(1:old_size)          = tmp_particles_d(1:old_size)
7880       grid_particles(k,j,i)%particles(old_size+1:new_size) = zero_particle
7881
7882       DEALLOCATE(tmp_particles_d)
7883
7884    ENDIF
7885    particles => grid_particles(k,j,i)%particles(1:new_size)
7886
7887    RETURN
7888   
7889 END SUBROUTINE realloc_particles_array
7890 
7891 
7892!------------------------------------------------------------------------------!
7893! Description:
7894! ------------
7895!> Not needed but allocated space for particles is dealloced.
7896!------------------------------------------------------------------------------!
7897 SUBROUTINE dealloc_particles_array
7898
7899 
7900    INTEGER(iwp) ::  i
7901    INTEGER(iwp) ::  j
7902    INTEGER(iwp) ::  k
7903    INTEGER(iwp) :: old_size        !<
7904    INTEGER(iwp) :: new_size        !<
7905
7906    LOGICAL                                        :: dealloc 
7907
7908    TYPE(particle_type), DIMENSION(:), ALLOCATABLE :: tmp_particles_d !<
7909    TYPE(particle_type), DIMENSION(500)            :: tmp_particles_s !<
7910
7911    DO  i = nxl, nxr
7912       DO  j = nys, nyn
7913          DO  k = nzb+1, nzt
7914!
7915!--          Determine number of active particles
7916             number_of_particles = prt_count(k,j,i)
7917!
7918!--          Determine allocated memory size
7919             old_size = SIZE( grid_particles(k,j,i)%particles )
7920!
7921!--          Check for large unused memory
7922             dealloc = ( ( number_of_particles < 1 .AND.         &
7923                           old_size            > 1 )  .OR.       &
7924                         ( number_of_particles > 1 .AND.         &
7925                           old_size - number_of_particles *                    &
7926                              ( 1.0_wp + 0.01_wp * alloc_factor ) > 0.0_wp ) )
7927
7928             IF ( dealloc )  THEN
7929                IF ( number_of_particles < 1 )  THEN
7930                   new_size = 1
7931                ELSE
7932                   new_size = INT( number_of_particles * ( 1.0_wp + 0.01_wp * alloc_factor ) )
7933                ENDIF
7934
7935                IF ( number_of_particles <= 500 )  THEN
7936
7937                   tmp_particles_s(1:number_of_particles) = grid_particles(k,j,i)%particles(1:number_of_particles)
7938
7939                   DEALLOCATE(grid_particles(k,j,i)%particles)
7940                   ALLOCATE(grid_particles(k,j,i)%particles(new_size))
7941
7942                   grid_particles(k,j,i)%particles(1:number_of_particles)          = tmp_particles_s(1:number_of_particles)
7943                   grid_particles(k,j,i)%particles(number_of_particles+1:new_size) = zero_particle
7944
7945                ELSE
7946
7947                   ALLOCATE(tmp_particles_d(number_of_particles))
7948                   tmp_particles_d(1:number_of_particles) = grid_particles(k,j,i)%particles(1:number_of_particles)
7949
7950                   DEALLOCATE(grid_particles(k,j,i)%particles)
7951                   ALLOCATE(grid_particles(k,j,i)%particles(new_size))
7952
7953                   grid_particles(k,j,i)%particles(1:number_of_particles)          = tmp_particles_d(1:number_of_particles)
7954                   grid_particles(k,j,i)%particles(number_of_particles+1:new_size) = zero_particle
7955
7956                   DEALLOCATE(tmp_particles_d)
7957
7958                ENDIF
7959
7960             ENDIF
7961          ENDDO
7962       ENDDO
7963    ENDDO
7964
7965 END SUBROUTINE dealloc_particles_array 
7966 
7967 
7968!------------------------------------------------------------------------------!
7969! Description:
7970! -----------
7971!> Routine for the whole processor
7972!> Sort all particles into the 8 respective subgrid boxes and free space of
7973!> particles which has been marked for deletion
7974!------------------------------------------------------------------------------!
7975   SUBROUTINE lpm_sort_and_delete
7976
7977       INTEGER(iwp) ::  i  !<
7978       INTEGER(iwp) ::  ip !<
7979       INTEGER(iwp) ::  is !<
7980       INTEGER(iwp) ::  j  !<
7981       INTEGER(iwp) ::  jp !<
7982       INTEGER(iwp) ::  kp !<
7983       INTEGER(iwp) ::  m  !<
7984       INTEGER(iwp) ::  n  !<
7985       INTEGER(iwp) ::  nn !<
7986       INTEGER(iwp) ::  sort_index  !<
7987
7988       INTEGER(iwp), DIMENSION(0:7) ::  sort_count  !<
7989
7990       TYPE(particle_type), DIMENSION(:,:), ALLOCATABLE ::  sort_particles    !<
7991
7992       CALL cpu_log( log_point_s(51), 'lpm_sort_and_delete', 'start' )
7993       IF ( TRIM(particle_interpolation)  == 'trilinear' ) THEN
7994          DO  ip = nxl, nxr
7995             DO  jp = nys, nyn
7996                DO  kp = nzb+1, nzt
7997                   number_of_particles = prt_count(kp,jp,ip)
7998                   IF ( number_of_particles <= 0 )  CYCLE
7999                   particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
8000                   nn = 0
8001                   sort_count = 0
8002                   ALLOCATE( sort_particles(number_of_particles, 0:7) )
8003
8004                   DO  n = 1, number_of_particles
8005                      sort_index = 0
8006
8007                      IF ( particles(n)%particle_mask )  THEN
8008                         nn = nn + 1
8009!
8010!--                      Sorting particles with a binary scheme
8011!--                      sort_index=111_2=7_10 -> particle at the left,south,bottom subgridbox
8012!--                      sort_index=000_2=0_10 -> particle at the right,north,top subgridbox
8013!--                      For this the center of the gridbox is calculated
8014                         i = (particles(n)%x + 0.5_wp * dx) * ddx
8015                         j = (particles(n)%y + 0.5_wp * dy) * ddy
8016
8017                         IF ( i == ip )  sort_index = sort_index + 4
8018                         IF ( j == jp )  sort_index = sort_index + 2
8019                         IF ( zu(kp) > particles(n)%z ) sort_index = sort_index + 1
8020
8021                         sort_count(sort_index) = sort_count(sort_index) + 1
8022                         m = sort_count(sort_index)
8023                         sort_particles(m,sort_index) = particles(n)
8024                         sort_particles(m,sort_index)%block_nr = sort_index
8025                      ENDIF
8026                   ENDDO
8027
8028                   nn = 0
8029                   DO is = 0,7
8030                      grid_particles(kp,jp,ip)%start_index(is) = nn + 1
8031                      DO n = 1,sort_count(is)
8032                         nn = nn + 1
8033                         particles(nn) = sort_particles(n,is)
8034                      ENDDO
8035                      grid_particles(kp,jp,ip)%end_index(is) = nn
8036                   ENDDO
8037
8038                   number_of_particles = nn
8039                   prt_count(kp,jp,ip) = number_of_particles
8040                   DEALLOCATE(sort_particles)
8041                ENDDO
8042             ENDDO
8043          ENDDO
8044
8045!--    In case of the simple interpolation method the particles must not
8046!--    be sorted in subboxes but particles marked for deletion must be
8047!--    deleted and number of particles must be recalculated
8048       ELSE
8049
8050          DO  ip = nxl, nxr
8051             DO  jp = nys, nyn
8052                DO  kp = nzb+1, nzt
8053
8054                   number_of_particles = prt_count(kp,jp,ip)
8055                   IF ( number_of_particles <= 0 )  CYCLE
8056                   particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
8057!
8058!--                repack particles array, i.e. delete particles and recalculate
8059!--                number of particles
8060                   CALL lpm_pack
8061                   prt_count(kp,jp,ip) = number_of_particles
8062                ENDDO
8063             ENDDO
8064          ENDDO
8065       ENDIF
8066       CALL cpu_log( log_point_s(51), 'lpm_sort_and_delete', 'stop' )
8067
8068    END SUBROUTINE lpm_sort_and_delete
8069
8070 
8071!------------------------------------------------------------------------------!
8072! Description:
8073! ------------
8074!> Move all particles not marked for deletion to lowest indices (packing)
8075!------------------------------------------------------------------------------!
8076    SUBROUTINE lpm_pack
8077
8078       INTEGER(iwp) ::  n       !<
8079       INTEGER(iwp) ::  nn      !<
8080!
8081!--    Find out elements marked for deletion and move data from highest index
8082!--    values to these free indices
8083       nn = number_of_particles
8084
8085       DO WHILE ( .NOT. particles(nn)%particle_mask )
8086          nn = nn-1
8087          IF ( nn == 0 )  EXIT
8088       ENDDO
8089
8090       IF ( nn > 0 )  THEN
8091          DO  n = 1, number_of_particles
8092             IF ( .NOT. particles(n)%particle_mask )  THEN
8093                particles(n) = particles(nn)
8094                nn = nn - 1
8095                DO WHILE ( .NOT. particles(nn)%particle_mask )
8096                   nn = nn-1
8097                   IF ( n == nn )  EXIT
8098                ENDDO
8099             ENDIF
8100             IF ( n == nn )  EXIT
8101          ENDDO
8102       ENDIF
8103
8104!
8105!--    The number of deleted particles has been determined in routines
8106!--    lpm_boundary_conds, lpm_droplet_collision, and lpm_exchange_horiz
8107       number_of_particles = nn
8108
8109    END SUBROUTINE lpm_pack 
8110
8111
8112!------------------------------------------------------------------------------!
8113! Description:
8114! ------------
8115!> Sort particles in each sub-grid box into two groups: particles that already
8116!> completed the LES timestep, and particles that need further timestepping to
8117!> complete the LES timestep.
8118!------------------------------------------------------------------------------!
8119    SUBROUTINE lpm_sort_timeloop_done
8120
8121       INTEGER(iwp) :: end_index     !< particle end index for each sub-box
8122       INTEGER(iwp) :: i             !< index of particle grid box in x-direction
8123       INTEGER(iwp) :: j             !< index of particle grid box in y-direction
8124       INTEGER(iwp) :: k             !< index of particle grid box in z-direction
8125       INTEGER(iwp) :: n             !< running index for number of particles
8126       INTEGER(iwp) :: nb            !< index of subgrid boux
8127       INTEGER(iwp) :: nf            !< indices for particles in each sub-box that already finalized their substeps
8128       INTEGER(iwp) :: nnf           !< indices for particles in each sub-box that need further treatment
8129       INTEGER(iwp) :: num_finalized !< number of particles in each sub-box that already finalized their substeps
8130       INTEGER(iwp) :: start_index   !< particle start index for each sub-box
8131
8132       TYPE(particle_type), DIMENSION(:), ALLOCATABLE :: sort_particles  !< temporary particle array
8133
8134       DO  i = nxl, nxr
8135          DO  j = nys, nyn
8136             DO  k = nzb+1, nzt
8137
8138                number_of_particles = prt_count(k,j,i)
8139                IF ( number_of_particles <= 0 )  CYCLE
8140                particles => grid_particles(k,j,i)%particles(1:number_of_particles)
8141
8142                DO  nb = 0, 7
8143!
8144!--                Obtain start and end index for each subgrid box
8145                   start_index = grid_particles(k,j,i)%start_index(nb)
8146                   end_index   = grid_particles(k,j,i)%end_index(nb)
8147!
8148!--                Allocate temporary array used for sorting.
8149                   ALLOCATE( sort_particles(start_index:end_index) )
8150!
8151!--                Determine number of particles already completed the LES
8152!--                timestep, and write them into a temporary array.
8153                   nf = start_index
8154                   num_finalized = 0
8155                   DO  n = start_index, end_index
8156                      IF ( dt_3d - particles(n)%dt_sum < 1E-8_wp )  THEN
8157                         sort_particles(nf) = particles(n)
8158                         nf                 = nf + 1
8159                         num_finalized      = num_finalized + 1
8160                      ENDIF
8161                   ENDDO
8162!
8163!--                Determine number of particles that not completed the LES
8164!--                timestep, and write them into a temporary array.
8165                   nnf = nf
8166                   DO  n = start_index, end_index
8167                      IF ( dt_3d - particles(n)%dt_sum > 1E-8_wp )  THEN
8168                         sort_particles(nnf) = particles(n)
8169                         nnf                 = nnf + 1
8170                      ENDIF
8171                   ENDDO
8172!
8173!--                Write back sorted particles
8174                   particles(start_index:end_index) =                          &
8175                                           sort_particles(start_index:end_index)
8176!
8177!--                Determine updated start_index, used to masked already
8178!--                completed particles.
8179                   grid_particles(k,j,i)%start_index(nb) =                     &
8180                                      grid_particles(k,j,i)%start_index(nb)    &
8181                                    + num_finalized
8182!
8183!--                Deallocate dummy array
8184                   DEALLOCATE ( sort_particles )
8185!
8186!--                Finally, if number of non-completed particles is non zero
8187!--                in any of the sub-boxes, set control flag appropriately.
8188                   IF ( nnf > nf )                                             &
8189                      grid_particles(k,j,i)%time_loop_done = .FALSE.
8190
8191                ENDDO
8192             ENDDO
8193          ENDDO
8194       ENDDO
8195
8196    END SUBROUTINE lpm_sort_timeloop_done 
8197
8198END MODULE lagrangian_particle_model_mod
Note: See TracBrowser for help on using the repository browser.