source: palm/trunk/SOURCE/lpm_droplet_collision.f90 @ 2101

Last change on this file since 2101 was 2101, checked in by suehring, 7 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 22.8 KB
Line 
1!> @file lpm_droplet_collision.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
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-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: lpm_droplet_collision.f90 2101 2017-01-05 16:42:31Z suehring $
27!
28! 2000 2016-08-20 18:09:15Z knoop
29! Forced header and separation lines into 80 columns
30!
31! 1884 2016-04-21 11:11:40Z hoffmann
32! Conservation of mass should only be checked if collisions took place.
33!
34! 1860 2016-04-13 13:21:28Z hoffmann
35! Interpolation of dissipation rate adjusted to more reasonable values.
36!
37! 1822 2016-04-07 07:49:42Z hoffmann
38! Integration of a new collision algortithm based on Shima et al. (2009) and
39! Soelch and Kaercher (2010) called all_or_nothing. The previous implemented
40! collision algorithm is called average_impact. Moreover, both algorithms are
41! now positive definit due to their construction, i.e., no negative weighting
42! factors should occur.
43!
44! 1682 2015-10-07 23:56:08Z knoop
45! Code annotations made doxygen readable
46!
47! 1359 2014-04-11 17:15:14Z hoffmann
48! New particle structure integrated.
49! Kind definition added to all floating point numbers.
50!
51! 1322 2014-03-20 16:38:49Z raasch
52! REAL constants defined as wp_kind
53!
54! 1320 2014-03-20 08:40:49Z raasch
55! ONLY-attribute added to USE-statements,
56! kind-parameters added to all INTEGER and REAL declaration statements,
57! kinds are defined in new module kinds,
58! revision history before 2012 removed,
59! comment fields (!:) to be used for variable explanations added to
60! all variable declaration statements
61!
62! 1092 2013-02-02 11:24:22Z raasch
63! unused variables removed
64!
65! 1071 2012-11-29 16:54:55Z franke
66! Calculation of Hall and Wang kernel now uses collision-coalescence formulation
67! proposed by Wang instead of the continuous collection equation (for more
68! information about new method see PALM documentation)
69! Bugfix: message identifiers added
70!
71! 1036 2012-10-22 13:43:42Z raasch
72! code put under GPL (PALM 3.9)
73!
74! 849 2012-03-15 10:35:09Z raasch
75! initial revision (former part of advec_particles)
76!
77!
78! Description:
79! ------------
80!> Calculates change in droplet radius by collision. Droplet collision is
81!> calculated for each grid box seperately. Collision is parameterized by
82!> using collision kernels. Two different kernels are available:
83!> Hall kernel: Kernel from Hall (1980, J. Atmos. Sci., 2486-2507), which
84!>              considers collision due to pure gravitational effects.
85!> Wang kernel: Beside gravitational effects (treated with the Hall-kernel) also
86!>              the effects of turbulence on the collision are considered using
87!>              parameterizations of Ayala et al. (2008, New J. Phys., 10,
88!>              075015) and Wang and Grabowski (2009, Atmos. Sci. Lett., 10,
89!>              1-8). This kernel includes three possible effects of turbulence:
90!>              the modification of the relative velocity between the droplets,
91!>              the effect of preferential concentration, and the enhancement of
92!>              collision efficiencies.
93!------------------------------------------------------------------------------!
94 SUBROUTINE lpm_droplet_collision (i,j,k)
95 
96
97
98    USE arrays_3d,                                                             &
99        ONLY:  diss, ql_v, ql_vp
100
101    USE cloud_parameters,                                                      &
102        ONLY:  rho_l
103
104    USE constants,                                                             &
105        ONLY:  pi
106
107    USE control_parameters,                                                    &
108        ONLY:  dt_3d, message_string, dz
109
110    USE cpulog,                                                                &
111        ONLY:  cpu_log, log_point_s
112
113    USE grid_variables,                                                        &
114        ONLY:  dx, dy
115
116    USE kinds
117
118    USE lpm_collision_kernels_mod,                                             &
119        ONLY:  ckernel, recalculate_kernel
120
121    USE particle_attributes,                                                   &
122        ONLY:  all_or_nothing, average_impact, dissipation_classes,            &
123               hall_kernel, iran_part, number_of_particles, particles,         &
124               particle_type, prt_count, use_kernel_tables, wang_kernel
125
126    USE random_function_mod,                                                   &
127        ONLY:  random_function
128
129    USE pegrid
130
131    IMPLICIT NONE
132
133    INTEGER(iwp) ::  eclass   !<
134    INTEGER(iwp) ::  i        !<
135    INTEGER(iwp) ::  j        !<
136    INTEGER(iwp) ::  k        !<
137    INTEGER(iwp) ::  n        !<
138    INTEGER(iwp) ::  m        !<
139    INTEGER(iwp) ::  rclass_l !<
140    INTEGER(iwp) ::  rclass_s !<
141
142    REAL(wp) ::  collection_probability  !< probability for collection
143    REAL(wp) ::  ddV                     !< inverse grid box volume
144    REAL(wp) ::  epsilon                 !< dissipation rate
145    REAL(wp) ::  factor_volume_to_mass   !< 4.0 / 3.0 * pi * rho_l
146    REAL(wp) ::  xm                      !< mean mass of droplet m
147    REAL(wp) ::  xn                      !< mean mass of droplet n
148
149    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight  !< weighting factor
150    REAL(wp), DIMENSION(:), ALLOCATABLE ::  mass    !< total mass of super droplet
151
152    CALL cpu_log( log_point_s(43), 'lpm_droplet_coll', 'start' )
153
154    number_of_particles   = prt_count(k,j,i)
155    factor_volume_to_mass = 4.0_wp / 3.0_wp * pi * rho_l 
156    ddV                   = 1 / ( dx * dy * dz )
157!
158!-- Collision requires at least one super droplet inside the box
159    IF ( number_of_particles > 0 )  THEN
160
161!
162!--    Now apply the different kernels
163       IF ( use_kernel_tables )  THEN
164!
165!--       Fast method with pre-calculated collection kernels for
166!--       discrete radius- and dissipation-classes.
167!--
168!--       Determine dissipation class index of this gridbox
169          IF ( wang_kernel )  THEN
170             eclass = INT( diss(k,j,i) * 1.0E4_wp / 600.0_wp * &
171                           dissipation_classes ) + 1
172             epsilon = diss(k,j,i)
173          ELSE
174             epsilon = 0.0_wp
175          ENDIF
176          IF ( hall_kernel  .OR.  epsilon * 1.0E4_wp < 0.001_wp )  THEN
177             eclass = 0   ! Hall kernel is used
178          ELSE
179             eclass = MIN( dissipation_classes, eclass )
180          ENDIF
181
182!
183!--       Droplet collision are calculated using collision-coalescence
184!--       formulation proposed by Wang (see PALM documentation)
185!--       Temporary fields for total mass of super-droplet and weighting factors
186!--       are allocated.
187          ALLOCATE(mass(1:number_of_particles), weight(1:number_of_particles))
188
189          mass(1:number_of_particles)   = particles(1:number_of_particles)%weight_factor * &
190                                          particles(1:number_of_particles)%radius**3     * &
191                                          factor_volume_to_mass
192          weight(1:number_of_particles) = particles(1:number_of_particles)%weight_factor
193
194          IF ( average_impact )  THEN  ! select collision algorithm
195
196             DO  n = 1, number_of_particles
197
198                rclass_l = particles(n)%class
199                xn       = mass(n) / weight(n)
200
201                DO  m = n, number_of_particles
202
203                   rclass_s = particles(m)%class
204                   xm       = mass(m) / weight(m)
205
206                   IF ( xm .LT. xn )  THEN
207                     
208!
209!--                   Particle n collects smaller particle m
210                      collection_probability = ckernel(rclass_l,rclass_s,eclass) * &
211                                               weight(n) * ddV * dt_3d
212
213                      mass(n)   = mass(n)   + mass(m)   * collection_probability
214                      weight(m) = weight(m) - weight(m) * collection_probability
215                      mass(m)   = mass(m)   - mass(m)   * collection_probability
216                   ELSEIF ( xm .GT. xn )  THEN 
217!
218!--                   Particle m collects smaller particle n
219                      collection_probability = ckernel(rclass_l,rclass_s,eclass) * &
220                                               weight(m) * ddV * dt_3d
221
222                      mass(m)   = mass(m)   + mass(n)   * collection_probability
223                      weight(n) = weight(n) - weight(n) * collection_probability
224                      mass(n)   = mass(n)   - mass(n)   * collection_probability
225                   ELSE
226!
227!--                   Same-size collections. If n = m, weight is reduced by the
228!--                   number of possible same-size collections; the total mass
229!--                   is not changed during same-size collection.
230!--                   Same-size collections of different
231!--                   particles ( n /= m ) are treated as same-size collections
232!--                   of ONE partilce with weight = weight(n) + weight(m) and
233!--                   mass = mass(n) + mass(m).
234!--                   Accordingly, each particle loses the same number of
235!--                   droplets to the other particle, but this has no effect on
236!--                   total mass mass, since the exchanged droplets have the
237!--                   same radius.
238
239!--                   Note: For m = n this equation is an approximation only
240!--                   valid for weight >> 1 (which is usually the case). The
241!--                   approximation is weight(n)-1 = weight(n).
242                      weight(n) = weight(n) - 0.5_wp * weight(n) *                &
243                                              ckernel(rclass_l,rclass_s,eclass) * &
244                                              weight(m) * ddV * dt_3d
245                      IF ( n .NE. m )  THEN
246                         weight(m) = weight(m) - 0.5_wp * weight(m) *                &
247                                                 ckernel(rclass_l,rclass_s,eclass) * &
248                                                 weight(n) * ddV * dt_3d
249                      ENDIF
250                   ENDIF
251
252                ENDDO
253
254                ql_vp(k,j,i) = ql_vp(k,j,i) + mass(n) / factor_volume_to_mass
255
256             ENDDO
257
258          ELSEIF ( all_or_nothing )  THEN  ! select collision algorithm
259
260             DO  n = 1, number_of_particles
261
262                rclass_l = particles(n)%class
263                xn       = mass(n) / weight(n) ! mean mass of droplet n
264
265                DO  m = n, number_of_particles
266
267                   rclass_s = particles(m)%class
268                   xm = mass(m) / weight(m) ! mean mass of droplet m
269
270                   IF ( weight(n) .LT. weight(m) )  THEN
271!
272!--                   Particle n collects weight(n) droplets of particle m 
273                      collection_probability = ckernel(rclass_l,rclass_s,eclass) * &
274                                               weight(m) * ddV * dt_3d
275
276                      IF ( collection_probability .GT. random_function( iran_part ) )  THEN
277                         mass(n)   = mass(n)   + weight(n) * xm
278                         weight(m) = weight(m) - weight(n)
279                         mass(m)   = mass(m)   - weight(n) * xm
280                      ENDIF
281
282                   ELSEIF ( weight(m) .LT. weight(n) )  THEN 
283!
284!--                   Particle m collects weight(m) droplets of particle n 
285                      collection_probability = ckernel(rclass_l,rclass_s,eclass) * &
286                                               weight(n) * ddV * dt_3d
287
288                      IF ( collection_probability .GT. random_function( iran_part ) )  THEN
289                         mass(m)   = mass(m)   + weight(m) * xn
290                         weight(n) = weight(n) - weight(m)
291                         mass(n)   = mass(n)   - weight(m) * xn
292                      ENDIF
293                   ELSE
294!
295!--                   Collisions of particles of the same weighting factor.
296!--                   Particle n collects 1/2 weight(n) droplets of particle m,
297!--                   particle m collects 1/2 weight(m) droplets of particle n.
298!--                   The total mass mass changes accordingly.
299!--                   If n = m, the first half of the droplets coalesces with the
300!--                   second half of the droplets; mass is unchanged because
301!--                   xm = xn for n = m.
302
303!--                   Note: For m = n this equation is an approximation only
304!--                   valid for weight >> 1 (which is usually the case). The
305!--                   approximation is weight(n)-1 = weight(n).
306                      collection_probability = ckernel(rclass_l,rclass_s,eclass) * &
307                                               weight(n) * ddV * dt_3d
308
309                      IF ( collection_probability .GT. random_function( iran_part ) )  THEN
310                         mass(n)   = mass(n)   + 0.5_wp * weight(n) * ( xm - xn )
311                         mass(m)   = mass(m)   + 0.5_wp * weight(m) * ( xn - xm )
312                         weight(n) = weight(n) - 0.5_wp * weight(m)
313                         weight(m) = weight(n)
314                      ENDIF
315                   ENDIF
316
317                ENDDO
318
319                ql_vp(k,j,i) = ql_vp(k,j,i) + mass(n) / factor_volume_to_mass
320
321             ENDDO
322
323          ENDIF
324
325
326
327
328          IF ( ANY(weight < 0.0_wp) )  THEN
329                WRITE( message_string, * ) 'negative weighting'
330                CALL message( 'lpm_droplet_collision', 'PA0028',      &
331                               2, 2, -1, 6, 1 )
332          ENDIF
333
334          particles(1:number_of_particles)%radius = ( mass(1:number_of_particles) /   &
335                                                      ( weight(1:number_of_particles) &
336                                                        * factor_volume_to_mass       &
337                                                      )                               &
338                                                    )**0.33333333333333_wp
339
340          particles(1:number_of_particles)%weight_factor = weight(1:number_of_particles)
341
342          DEALLOCATE(weight, mass)
343
344       ELSEIF ( .NOT. use_kernel_tables )  THEN
345!
346!--       Collection kernels are calculated for every new
347!--       grid box. First, allocate memory for kernel table.
348!--       Third dimension is 1, because table is re-calculated for
349!--       every new dissipation value.
350          ALLOCATE( ckernel(1:number_of_particles,1:number_of_particles,1:1) )
351!
352!--       Now calculate collection kernel for this box. Note that
353!--       the kernel is based on the previous time step
354          CALL recalculate_kernel( i, j, k )
355!
356!--       Droplet collision are calculated using collision-coalescence
357!--       formulation proposed by Wang (see PALM documentation)
358!--       Temporary fields for total mass of super-droplet and weighting factors
359!--       are allocated.
360          ALLOCATE(mass(1:number_of_particles), weight(1:number_of_particles))
361
362          mass(1:number_of_particles) = particles(1:number_of_particles)%weight_factor * &
363                                        particles(1:number_of_particles)%radius**3     * &
364                                        factor_volume_to_mass
365
366          weight(1:number_of_particles) = particles(1:number_of_particles)%weight_factor
367
368          IF ( average_impact )  THEN  ! select collision algorithm
369
370             DO  n = 1, number_of_particles
371
372                xn = mass(n) / weight(n) ! mean mass of droplet n
373
374                DO  m = n, number_of_particles
375
376                   xm = mass(m) / weight(m) !mean mass of droplet m
377
378                   IF ( xm .LT. xn )  THEN
379!
380!--                   Particle n collects smaller particle m
381                      collection_probability = ckernel(n,m,1) * weight(n) *    &
382                                               ddV * dt_3d
383
384                      mass(n)   = mass(n)   + mass(m)   * collection_probability
385                      weight(m) = weight(m) - weight(m) * collection_probability
386                      mass(m)   = mass(m)   - mass(m)   * collection_probability
387                   ELSEIF ( xm .GT. xn )  THEN 
388!
389!--                   Particle m collects smaller particle n
390                      collection_probability = ckernel(n,m,1) * weight(m) *    &
391                                               ddV * dt_3d
392
393                      mass(m)   = mass(m)   + mass(n)   * collection_probability
394                      weight(n) = weight(n) - weight(n) * collection_probability
395                      mass(n)   = mass(n)   - mass(n)   * collection_probability
396                   ELSE
397!
398!--                   Same-size collections. If n = m, weight is reduced by the
399!--                   number of possible same-size collections; the total mass
400!--                   mass is not changed during same-size collection.
401!--                   Same-size collections of different
402!--                   particles ( n /= m ) are treated as same-size collections
403!--                   of ONE partilce with weight = weight(n) + weight(m) and
404!--                   mass = mass(n) + mass(m).
405!--                   Accordingly, each particle loses the same number of
406!--                   droplets to the other particle, but this has no effect on
407!--                   total mass mass, since the exchanged droplets have the
408!--                   same radius.
409!--
410!--                   Note: For m = n this equation is an approximation only
411!--                   valid for weight >> 1 (which is usually the case). The
412!--                   approximation is weight(n)-1 = weight(n).
413                      weight(n) = weight(n) - 0.5_wp * weight(n) *             &
414                                              ckernel(n,m,1) * weight(m) *     &
415                                              ddV * dt_3d
416                      IF ( n .NE. m )  THEN
417                         weight(m) = weight(m) - 0.5_wp * weight(m) *          &
418                                                 ckernel(n,m,1) * weight(n) *  &
419                                                 ddV * dt_3d
420                      ENDIF
421                   ENDIF
422
423
424                ENDDO
425
426                ql_vp(k,j,i) = ql_vp(k,j,i) + mass(n) / factor_volume_to_mass
427
428             ENDDO
429
430          ELSEIF ( all_or_nothing )  THEN  ! select collision algorithm
431
432             DO  n = 1, number_of_particles
433
434                xn = mass(n) / weight(n) ! mean mass of droplet n
435
436                DO  m = n, number_of_particles
437
438                   xm = mass(m) / weight(m) !mean mass of droplet m
439
440                   IF ( weight(n) .LT. weight(m) )  THEN
441!
442!--                   Particle n collects smaller particle m
443                      collection_probability = ckernel(n,m,1) * weight(m) *    &
444                                               ddV * dt_3d
445
446                      IF ( collection_probability .GT. random_function( iran_part ) )  THEN
447                         mass(n) = mass(n) + weight(n) * xm 
448                         weight(m)    = weight(m)    - weight(n)
449                         mass(m) = mass(m) - weight(n) * xm
450                      ENDIF
451
452                   ELSEIF ( weight(m) .LT. weight(n) )  THEN
453!
454!--                   Particle m collects smaller particle n
455                      collection_probability = ckernel(n,m,1) * weight(n) *    &
456                                               ddV * dt_3d
457
458                      IF ( collection_probability .GT. random_function( iran_part ) )  THEN
459                         mass(m) = mass(m) + weight(m) * xn
460                         weight(n)    = weight(n)    - weight(m)
461                         mass(n) = mass(n) - weight(m) * xn
462                      ENDIF
463                   ELSE
464!
465!--                   Collisions of particles of the same weighting factor.
466!--                   Particle n collects 1/2 weight(n) droplets of particle m,
467!--                   particle m collects 1/2 weight(m) droplets of particle n.
468!--                   The total mass mass changes accordingly.
469!--                   If n = m, the first half of the droplets coalesces with the
470!--                   second half of the droplets; mass is unchanged because
471!--                   xm = xn for n = m.
472!--
473!--                   Note: For m = n this equation is an approximation only
474!--                   valid for weight >> 1 (which is usually the case). The
475!--                   approximation is weight(n)-1 = weight(n).
476                      collection_probability = ckernel(n,m,1) * weight(n) *    &
477                                               ddV * dt_3d
478
479                      IF ( collection_probability .GT. random_function( iran_part ) )  THEN
480                         mass(n)   = mass(n)   + 0.5_wp * weight(n) * ( xm - xn )
481                         mass(m)   = mass(m)   + 0.5_wp * weight(m) * ( xn - xm )
482                         weight(n) = weight(n) - 0.5_wp * weight(m)
483                         weight(m) = weight(n)
484                      ENDIF
485                   ENDIF
486
487
488                ENDDO
489
490                ql_vp(k,j,i) = ql_vp(k,j,i) + mass(n) / factor_volume_to_mass
491
492             ENDDO
493
494          ENDIF
495
496          IF ( ANY(weight < 0.0_wp) )  THEN
497                WRITE( message_string, * ) 'negative weighting'
498                CALL message( 'lpm_droplet_collision', 'PA0028',      &
499                               2, 2, -1, 6, 1 )
500          ENDIF
501
502          particles(1:number_of_particles)%radius = ( mass(1:number_of_particles) /   &
503                                                      ( weight(1:number_of_particles) &
504                                                        * factor_volume_to_mass       &
505                                                      )                               &
506                                                    )**0.33333333333333_wp
507
508          particles(1:number_of_particles)%weight_factor = weight(1:number_of_particles)
509
510          DEALLOCATE( weight, mass, ckernel )
511
512       ENDIF
513 
514!
515!--    Check if LWC is conserved during collision process
516       IF ( ql_v(k,j,i) /= 0.0_wp )  THEN
517          IF ( ql_vp(k,j,i) / ql_v(k,j,i) >= 1.0001_wp  .OR.                      &
518               ql_vp(k,j,i) / ql_v(k,j,i) <= 0.9999_wp )  THEN
519             WRITE( message_string, * ) ' LWC is not conserved during',           &
520                                        ' collision! ',                           &
521                                        ' LWC after condensation: ', ql_v(k,j,i), &
522                                        ' LWC after collision: ', ql_vp(k,j,i)
523             CALL message( 'lpm_droplet_collision', 'PA0040', 2, 2, -1, 6, 1 )
524          ENDIF
525       ENDIF
526
527    ENDIF
528 
529    CALL cpu_log( log_point_s(43), 'lpm_droplet_coll', 'stop' )
530
531 END SUBROUTINE lpm_droplet_collision
Note: See TracBrowser for help on using the repository browser.