source: palm/trunk/SOURCE/lpm_collision_kernels.f90 @ 1071

Last change on this file since 1071 was 1071, checked in by franke, 11 years ago

ventilation effect for cloud droplets included, calculation of cloud droplet collisions now uses formulation by Wang, bugfixes in Rosenbrock method and in calculation of collision efficiencies

  • Property svn:keywords set to Id
File size: 36.1 KB
Line 
1 MODULE lpm_collision_kernels_mod
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! Bugfix: collision efficiencies for Hall kernel should not be < 1.0E-20
23!
24! Former revisions:
25! -----------------
26! $Id: lpm_collision_kernels.f90 1071 2012-11-29 16:54:55Z franke $
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! 1007 2012-09-19 14:30:36Z franke
32! converted all units to SI units and replaced some parameters by corresponding
33! PALM parameters
34! Bugfix: factor in calculation of enhancement factor for collision efficencies
35! changed from 10. to 1.0
36!
37! 849 2012-03-15 10:35:09Z raasch
38! routine collision_efficiency_rogers added (moved from former advec_particles
39! to here)
40!
41! 835 2012-02-22 11:21:19Z raasch $
42! Bugfix: array diss can be used only in case of Wang kernel
43!
44! 828 2012-02-21 12:00:36Z raasch
45! code has been completely reformatted, routine colker renamed
46! recalculate_kernel,
47! routine init_kernels added, radius is now communicated to the collision
48! routines by array radclass
49!
50! Bugfix: transformation factor for dissipation changed from 1E5 to 1E4
51!
52! 825 2012-02-19 03:03:44Z raasch
53! routine renamed from wang_kernel to lpm_collision_kernels,
54! turbulence_effects on collision replaced by wang_kernel
55!
56! 799 2011-12-21 17:48:03Z franke
57! speed optimizations and formatting
58! Bugfix: iq=1 is not allowed (routine effic)
59! Bugfix: replaced stop by ec=0.0 in case of very small ec (routine effic)
60!
61! 790 2011-11-29 03:11:20Z raasch
62! initial revision
63!
64! Description:
65! ------------
66! This module calculates collision efficiencies either due to pure gravitational
67! effects (Hall kernel, see Hall, 1980: J. Atmos. Sci., 2486-2507) or
68! including the effects of (SGS) turbulence (Wang kernel, see Wang and
69! Grabowski, 2009: Atmos. Sci. Lett., 10, 1-8). The original code has been
70! provided by L.-P. Wang but is substantially reformatted and speed optimized
71! here.
72!
73! ATTENTION:
74! Physical quantities (like g, densities, etc.) used in this module still
75! have to be adjusted to those values used in the main PALM code.
76! Also, quantities in CGS-units should be converted to SI-units eventually.
77!------------------------------------------------------------------------------!
78
79    USE arrays_3d
80    USE cloud_parameters
81    USE constants
82    USE particle_attributes
83    USE pegrid
84
85
86    IMPLICIT NONE
87
88    PRIVATE
89
90    PUBLIC  ckernel, collision_efficiency_rogers, init_kernels, &
91            rclass_lbound, rclass_ubound, recalculate_kernel
92
93    REAL ::  epsilon, eps2, rclass_lbound, rclass_ubound, urms, urms2
94
95    REAL, DIMENSION(:),   ALLOCATABLE ::  epsclass, radclass, winf
96    REAL, DIMENSION(:,:), ALLOCATABLE ::  ec, ecf, gck, hkernel, hwratio
97    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  ckernel
98
99    SAVE
100
101!
102!-- Public interfaces
103    INTERFACE collision_efficiency_rogers
104       MODULE PROCEDURE collision_efficiency_rogers
105    END INTERFACE collision_efficiency_rogers
106
107    INTERFACE init_kernels
108       MODULE PROCEDURE init_kernels
109    END INTERFACE init_kernels
110
111    INTERFACE recalculate_kernel
112       MODULE PROCEDURE recalculate_kernel
113    END INTERFACE recalculate_kernel
114
115
116    CONTAINS
117
118
119    SUBROUTINE init_kernels
120!------------------------------------------------------------------------------!
121! Initialization of the collision efficiency matrix with fixed radius and
122! dissipation classes, calculated at simulation start only.
123!------------------------------------------------------------------------------!
124
125       IMPLICIT NONE
126
127       INTEGER ::  i, j, k
128
129
130!
131!--    Calculate collision efficiencies for fixed radius- and dissipation
132!--    classes
133       IF ( collision_kernel(6:9) == 'fast' )  THEN
134
135          ALLOCATE( ckernel(1:radius_classes,1:radius_classes,               &
136                    0:dissipation_classes), epsclass(1:dissipation_classes), &
137                    radclass(1:radius_classes) )
138
139!
140!--       Calculate the radius class bounds with logarithmic distances
141!--       in the interval [1.0E-6, 2.0E-4] m
142          rclass_lbound = LOG( 1.0E-6 )
143          rclass_ubound = LOG( 2.0E-4 )
144          radclass(1)   = 1.0E-6
145          DO  i = 2, radius_classes
146             radclass(i) = EXP( rclass_lbound +                                &
147                                ( rclass_ubound - rclass_lbound ) * ( i-1.0 ) /&
148                                ( radius_classes - 1.0 ) )
149!             IF ( myid == 0 )  THEN
150!                PRINT*, 'i=', i, ' r = ', radclass(i)*1.0E6
151!             ENDIF
152          ENDDO
153
154!
155!--       Set the class bounds for dissipation in interval [0.0, 0.1] m**2/s**3
156          DO  i = 1, dissipation_classes
157             epsclass(i) = 0.1 * REAL( i ) / dissipation_classes
158!             IF ( myid == 0 )  THEN
159!                PRINT*, 'i=', i, ' eps = ', epsclass(i)
160!             ENDIF
161          ENDDO
162!
163!--       Calculate collision efficiencies of the Wang/ayala kernel
164          ALLOCATE( ec(1:radius_classes,1:radius_classes),  &
165                    ecf(1:radius_classes,1:radius_classes), &
166                    gck(1:radius_classes,1:radius_classes), &
167                    winf(1:radius_classes) )
168
169          DO  k = 1, dissipation_classes
170
171             epsilon = epsclass(k)
172             urms    = 2.02 * ( epsilon / 0.04 )**( 1.0 / 3.0 )
173
174             CALL turbsd
175             CALL turb_enhance_eff
176             CALL effic
177
178             DO  j = 1, radius_classes
179                DO  i = 1, radius_classes
180                   ckernel(i,j,k) = ec(i,j) * gck(i,j) * ecf(i,j)
181                ENDDO
182             ENDDO
183
184          ENDDO
185
186!
187!--       Calculate collision efficiencies of the Hall kernel
188          ALLOCATE( hkernel(1:radius_classes,1:radius_classes), &
189                    hwratio(1:radius_classes,1:radius_classes) )
190
191          CALL fallg
192          CALL effic
193
194          DO  j = 1, radius_classes
195             DO  i =  1, radius_classes
196                hkernel(i,j) = pi * ( radclass(j) + radclass(i) )**2 &
197                                  * ec(i,j) * ABS( winf(j) - winf(i) )
198                ckernel(i,j,0) = hkernel(i,j)  ! hall kernel stored on index 0
199              ENDDO
200          ENDDO
201
202!
203!--       Test output of efficiencies
204          IF ( j == -1 )  THEN
205
206             PRINT*, '*** Hall kernel'
207             WRITE ( *,'(5X,20(F4.0,1X))' ) ( radclass(i)*1.0E6, &
208                                              i = 1,radius_classes )
209             DO  j = 1, radius_classes
210                WRITE ( *,'(F4.0,1X,20(F8.4,1X))' ) radclass(j),  &
211                                          ( hkernel(i,j), i = 1,radius_classes )
212             ENDDO
213
214             DO  k = 1, dissipation_classes
215                DO  i = 1, radius_classes
216                   DO  j = 1, radius_classes
217                      IF ( hkernel(i,j) == 0.0 )  THEN
218                         hwratio(i,j) = 9999999.9
219                      ELSE
220                         hwratio(i,j) = ckernel(i,j,k) / hkernel(i,j)
221                      ENDIF
222                   ENDDO
223                ENDDO
224
225                PRINT*, '*** epsilon = ', epsclass(k)
226                WRITE ( *,'(5X,20(F4.0,1X))' ) ( radclass(i)*1.0E6, &
227                                                 i = 1,radius_classes )
228                DO  j = 1, radius_classes
229!                   WRITE ( *,'(F4.0,1X,20(F4.2,1X))' ) radclass(j)*1.0E6, &
230!                                       ( ckernel(i,j,k), i = 1,radius_classes )
231                   WRITE ( *,'(F4.0,1X,20(F8.4,1X))' ) radclass(j)*1.0E6, &
232                                          ( hwratio(i,j), i = 1,radius_classes )
233                ENDDO
234             ENDDO
235
236          ENDIF
237
238          DEALLOCATE( ec, ecf, epsclass, gck, hkernel, winf )
239
240       ELSEIF( collision_kernel == 'hall'  .OR.  collision_kernel == 'wang' ) &
241       THEN
242!
243!--       Initial settings for Hall- and Wang-Kernel
244!--       To be done: move here parts from turbsd, fallg, ecoll, etc.
245       ENDIF
246
247    END SUBROUTINE init_kernels
248
249
250!------------------------------------------------------------------------------!
251! Calculation of collision kernels during each timestep and for each grid box
252!------------------------------------------------------------------------------!
253    SUBROUTINE recalculate_kernel( i1, j1, k1 )
254
255       USE arrays_3d
256       USE cloud_parameters
257       USE constants
258       USE cpulog
259       USE indices
260       USE interfaces
261       USE particle_attributes
262
263       IMPLICIT NONE
264
265       INTEGER ::  i, i1, j, j1, k1, pend, pstart
266
267
268       pstart = prt_start_index(k1,j1,i1)
269       pend   = prt_start_index(k1,j1,i1) + prt_count(k1,j1,i1) - 1
270       radius_classes = prt_count(k1,j1,i1)
271
272       ALLOCATE( ec(1:radius_classes,1:radius_classes), &
273                 radclass(1:radius_classes), winf(1:radius_classes) )
274
275!
276!--    Store particle radii on the radclass array
277       radclass(1:radius_classes) = particles(pstart:pend)%radius
278
279       IF ( wang_kernel )  THEN
280          epsilon = diss(k1,j1,i1)   ! dissipation rate in m**2/s**3
281       ELSE
282          epsilon = 0.0
283       ENDIF
284       urms    = 2.02 * ( epsilon / 0.04 )**( 0.33333333333 )
285
286       IF ( wang_kernel  .AND.  epsilon > 1.0E-7 )  THEN
287!
288!--       Call routines to calculate efficiencies for the Wang kernel
289          ALLOCATE( gck(1:radius_classes,1:radius_classes), &
290                    ecf(1:radius_classes,1:radius_classes) )
291
292          CALL turbsd
293          CALL turb_enhance_eff
294          CALL effic
295
296          DO  j = 1, radius_classes
297             DO  i =  1, radius_classes
298                ckernel(pstart+i-1,pstart+j-1,1) = ec(i,j) * gck(i,j) * ecf(i,j)
299             ENDDO
300          ENDDO
301
302          DEALLOCATE( gck, ecf )
303
304       ELSE
305!
306!--       Call routines to calculate efficiencies for the Hall kernel
307          CALL fallg
308          CALL effic
309
310          DO  j = 1, radius_classes
311             DO  i =  1, radius_classes
312                ckernel(pstart+i-1,pstart+j-1,1) = pi *                       &
313                                          ( radclass(j) + radclass(i) )**2    &
314                                          * ec(i,j) * ABS( winf(j) - winf(i) )
315             ENDDO
316          ENDDO
317
318       ENDIF
319
320       DEALLOCATE( ec, radclass, winf )
321
322    END SUBROUTINE recalculate_kernel
323
324
325!------------------------------------------------------------------------------!
326! Calculation of gck
327! This is from Aayala 2008b, page 37ff.
328! Necessary input parameters: water density, radii of droplets, air density,
329! air viscosity, turbulent dissipation rate, taylor microscale reynolds number,
330! gravitational acceleration  --> to be replaced by PALM parameters
331!------------------------------------------------------------------------------!
332    SUBROUTINE turbsd
333
334       USE constants
335       USE cloud_parameters
336       USE particle_attributes
337       USE arrays_3d
338       USE control_parameters
339
340       IMPLICIT NONE
341
342       INTEGER ::  i, j
343
344       LOGICAL, SAVE ::  first = .TRUE.
345
346       REAL ::  ao, ao_gr, bbb, be, b1, b2, ccc, c1, c1_gr, c2, d1, d2, eta, &
347                e1, e2, fao_gr, fr, grfin, lambda, lambda_re, lf, rc, rrp,   &
348                sst, tauk, tl, t2, tt, t1, vk, vrms1xy, vrms2xy, v1, v1v2xy, &
349                v1xysq, v2, v2xysq, wrfin, wrgrav2, wrtur2xy, xx, yy, z
350
351       REAL, DIMENSION(1:radius_classes) ::  st, tau
352
353
354!
355!--    Initial assignment of constants
356       IF ( first )  THEN
357
358          first = .FALSE.
359
360       ENDIF
361
362       lambda    = urms * SQRT( 15.0 * molecular_viscosity / epsilon )    ! in m
363       lambda_re = urms**2 * SQRT( 15.0 / epsilon / molecular_viscosity )
364       tl        = urms**2 / epsilon                       ! in s
365       lf        = 0.5 * urms**3 / epsilon                 ! in m
366       tauk      = SQRT( molecular_viscosity / epsilon )                  ! in s
367       eta       = ( molecular_viscosity**3 / epsilon )**0.25             ! in m
368       vk        = eta / tauk
369
370       ao = ( 11.0 + 7.0 * lambda_re ) / ( 205.0 + lambda_re )
371       tt = SQRT( 2.0 * lambda_re / ( SQRT( 15.0 ) * ao ) ) * tauk   ! in s
372
373       CALL fallg    ! gives winf in m/s
374
375       DO  i = 1, radius_classes
376          tau(i) = winf(i) / g    ! in s
377          st(i)  = tau(i) / tauk
378       ENDDO
379
380!
381!--    Calculate wr (from Aayala 2008b, page 38f)
382       z   = tt / tl
383       be  = SQRT( 2.0 ) * lambda / lf
384       bbb = SQRT( 1.0 - 2.0 * be**2 )
385       d1  = ( 1.0 + bbb ) / ( 2.0 * bbb )
386       e1  = lf * ( 1.0 + bbb ) * 0.5   ! in m
387       d2  = ( 1.0 - bbb ) * 0.5 / bbb
388       e2  = lf * ( 1.0 - bbb ) * 0.5   ! in m
389       ccc = SQRT( 1.0 - 2.0 * z**2 )
390       b1  = ( 1.0 + ccc ) * 0.5 / ccc
391       c1  = tl * ( 1.0 + ccc ) * 0.5   ! in s
392       b2  = ( 1.0 - ccc ) * 0.5 / ccc
393       c2  = tl * ( 1.0 - ccc ) * 0.5   ! in s
394
395       DO  i = 1, radius_classes
396
397          v1 = winf(i)        ! in m/s
398          t1 = tau(i)         ! in s
399
400          DO  j = 1, i
401             rrp = radclass(i) + radclass(j)
402             v2  = winf(j)                                 ! in m/s
403             t2  = tau(j)                                  ! in s
404
405             v1xysq  = b1 * d1 * phi_w(c1,e1,v1,t1) - b1 * d2 * phi_w(c1,e2,v1,t1) &
406                     - b2 * d1 * phi_w(c2,e1,v1,t1) + b2 * d2 * phi_w(c2,e2,v1,t1)
407             v1xysq  = v1xysq * urms**2 / t1                ! in m**2/s**2
408             vrms1xy = SQRT( v1xysq )                       ! in m/s
409
410             v2xysq  = b1 * d1 * phi_w(c1,e1,v2,t2) - b1 * d2 * phi_w(c1,e2,v2,t2) &
411                     - b2 * d1 * phi_w(c2,e1,v2,t2) + b2 * d2 * phi_w(c2,e2,v2,t2)
412             v2xysq  = v2xysq * urms**2 / t2                ! in m**2/s**2
413             vrms2xy = SQRT( v2xysq )                       ! in m/s
414
415             IF ( winf(i) >= winf(j) )  THEN
416                v1 = winf(i)
417                t1 = tau(i)
418                v2 = winf(j)
419                t2 = tau(j)
420             ELSE
421                v1 = winf(j)
422                t1 = tau(j)
423                v2 = winf(i)
424                t2 = tau(i)
425             ENDIF
426
427             v1v2xy   =  b1 * d1 * zhi(c1,e1,v1,t1,v2,t2) - &
428                         b1 * d2 * zhi(c1,e2,v1,t1,v2,t2) - &
429                         b2 * d1 * zhi(c2,e1,v1,t1,v2,t2) + &
430                         b2 * d2* zhi(c2,e2,v1,t1,v2,t2)
431             fr       = d1 * EXP( -rrp / e1 ) - d2 * EXP( -rrp / e2 )
432             v1v2xy   = v1v2xy * fr * urms**2 / tau(i) / tau(j)  ! in m**2/s**2
433             wrtur2xy = vrms1xy**2 + vrms2xy**2 - 2.0 * v1v2xy   ! in m**2/s**2
434             IF ( wrtur2xy < 0.0 )  wrtur2xy = 0.0
435             wrgrav2  = pi / 8.0 * ( winf(j) - winf(i) )**2
436             wrfin    = SQRT( ( 2.0 / pi ) * ( wrtur2xy + wrgrav2) )   ! in m/s
437
438!
439!--          Calculate gr
440             IF ( st(j) > st(i) )  THEN
441                sst = st(j)
442             ELSE
443                sst = st(i)
444             ENDIF
445
446             xx = -0.1988 * sst**4 + 1.5275 * sst**3 - 4.2942 * sst**2 + &
447                   5.3406 * sst
448             IF ( xx < 0.0 )  xx = 0.0
449             yy = 0.1886 * EXP( 20.306 / lambda_re )
450
451             c1_gr  =  xx / ( g / vk * tauk )**yy
452
453             ao_gr  = ao + ( pi / 8.0) * ( g / vk * tauk )**2
454             fao_gr = 20.115 * SQRT( ao_gr / lambda_re )
455             rc     = SQRT( fao_gr * ABS( st(j) - st(i) ) ) * eta   ! in cm
456
457             grfin  = ( ( eta**2 + rc**2 ) / ( rrp**2 + rc**2) )**( c1_gr*0.5 )
458             IF ( grfin < 1.0 )  grfin = 1.0
459
460             gck(i,j) = 2.0 * pi * rrp**2 * wrfin * grfin           ! in cm**3/s
461             gck(j,i) = gck(i,j)
462
463          ENDDO
464       ENDDO
465
466    END SUBROUTINE turbsd
467
468
469!------------------------------------------------------------------------------!
470! phi_w as a function
471!------------------------------------------------------------------------------!
472    REAL FUNCTION phi_w( a, b, vsett, tau0 )
473
474       IMPLICIT NONE
475
476       REAL ::  a, aa1, b, tau0, vsett
477
478       aa1 = 1.0 / tau0 + 1.0 / a + vsett / b
479       phi_w = 1.0 / aa1  - 0.5 * vsett / b / aa1**2  ! in s
480
481    END FUNCTION phi_w
482
483
484!------------------------------------------------------------------------------!
485! zhi as a function
486!------------------------------------------------------------------------------!
487    REAL FUNCTION zhi( a, b, vsett1, tau1, vsett2, tau2 )
488
489       IMPLICIT NONE
490
491       REAL ::  a, aa1, aa2, aa3, aa4, aa5, aa6, b, tau1, tau2, vsett1, vsett2
492
493       aa1 = vsett2 / b - 1.0 / tau2 - 1.0 / a
494       aa2 = vsett1 / b + 1.0 / tau1 + 1.0 / a
495       aa3 = ( vsett1 - vsett2 ) / b + 1.0 / tau1 + 1.0 / tau2
496       aa4 = ( vsett2 / b )**2 - ( 1.0 / tau2 + 1.0 / a )**2
497       aa5 = vsett2 / b + 1.0 / tau2 + 1.0 / a
498       aa6 = 1.0 / tau1 - 1.0 / a + ( 1.0 / tau2 + 1.0 / a) * vsett1 / vsett2
499       zhi = (1.0 / aa1 - 1.0 / aa2 ) * ( vsett1 - vsett2 ) * 0.5 / b / aa3**2 &
500           + (4.0 / aa4 - 1.0 / aa5**2 - 1.0 / aa1**2 ) * vsett2 * 0.5 / b /aa6&
501           + (2.0 * ( b / aa2 - b / aa1 ) - vsett1 / aa2**2 + vsett2 / aa1**2 )&
502           * 0.5 / b / aa3      ! in s**2
503
504    END FUNCTION zhi
505
506
507!------------------------------------------------------------------------------!
508! Calculation of terminal velocity winf following Equations 10-138 to 10-145
509! from (Pruppacher and Klett, 1997)
510!------------------------------------------------------------------------------!
511    SUBROUTINE fallg
512
513       USE constants
514       USE cloud_parameters
515       USE particle_attributes
516       USE arrays_3d
517       USE control_parameters
518
519       IMPLICIT NONE
520
521       INTEGER ::  i, j
522
523       LOGICAL, SAVE ::  first = .TRUE.
524
525       REAL, SAVE ::  cunh, eta, phy, py, rho_a, sigma, stb, stok, &
526                      t0, xlamb
527
528       REAL ::  bond, x, xrey, y
529
530       REAL, DIMENSION(1:7), SAVE  ::  b
531       REAL, DIMENSION(1:6), SAVE  ::  c
532
533!
534!--    Initial assignment of constants
535       IF ( first )  THEN
536
537          first = .FALSE.
538          b = (/  -0.318657E1,  0.992696E0, -0.153193E-2, -0.987059E-3, &
539                 -0.578878E-3, 0.855176E-4, -0.327815E-5 /)
540          c = (/  -0.500015E1,  0.523778E1,  -0.204914E1,   0.475294E0, &
541                 -0.542819E-1, 0.238449E-2 /)
542
543!
544!--       Parameter values for p = 1013,25 hPa and T = 293,15 K
545          eta   = 1.818E-5         ! in kg/(m s)
546          xlamb = 6.6E-8           ! in m
547          rho_a = 1.204            ! in kg/m**3
548          cunh  = 1.26 * xlamb     ! in m
549          sigma = 0.07363          ! in kg/s**2
550          stok  = 2.0  * g * ( rho_l - rho_a ) / ( 9.0 * eta ) ! in 1/(m s)
551          stb   = 32.0 * rho_a * ( rho_l - rho_a) * g / (3.0 * eta * eta)
552          phy   = sigma**3 * rho_a**2 / ( eta**4 * g * ( rho_l - rho_a ) )
553          py    = phy**( 1.0 / 6.0 )
554
555       ENDIF
556
557       DO  j = 1, radius_classes
558
559          IF ( radclass(j) <= 1.0E-5 ) THEN
560
561             winf(j) = stok * ( radclass(j)**2 + cunh * radclass(j) )
562
563          ELSEIF ( radclass(j) > 1.0E-5  .AND.  radclass(j) <= 5.35E-4 )  THEN
564
565             x = LOG( stb * radclass(j)**3 )
566             y = 0.0
567
568             DO  i = 1, 7
569                y = y + b(i) * x**(i-1)
570             ENDDO
571!
572!--          Note: this Eq. is wrong in (Pruppacher and Klett, 1997, p. 418)
573!--          for correct version see (Beard, 1976)
574             xrey = ( 1.0 + cunh / radclass(j) ) * EXP( y ) 
575
576             winf(j) = xrey * eta / ( 2.0 * rho_a * radclass(j) )
577
578          ELSEIF ( radclass(j) > 5.35E-4 )  THEN
579
580             IF ( radclass(j) > 0.0035 )  THEN
581                bond = g * ( rho_l - rho_a ) * 0.0035**2 / sigma
582             ELSE
583               bond = g * ( rho_l - rho_a ) * radclass(j)**2 / sigma
584             ENDIF
585
586             x = LOG( 16.0 * bond * py / 3.0 )
587             y = 0.0
588
589             DO  i = 1, 6
590                y = y + c(i) * x**(i-1)
591             ENDDO
592
593             xrey = py * EXP( y )
594
595             IF ( radclass(j) > 0.0035 )  THEN
596                winf(j) = xrey * eta / ( 2.0 * rho_a * 0.0035 )
597             ELSE
598                winf(j) = xrey * eta / ( 2.0 * rho_a * radclass(j) )
599             ENDIF
600
601          ENDIF
602
603       ENDDO
604
605    END SUBROUTINE fallg
606
607
608!------------------------------------------------------------------------------!
609! Calculation of collision efficiencies for the Hall kernel
610!------------------------------------------------------------------------------!
611    SUBROUTINE effic
612
613       USE arrays_3d
614       USE cloud_parameters
615       USE constants
616       USE particle_attributes
617
618       IMPLICIT NONE
619
620       INTEGER ::  i, iq, ir, j, k, kk
621
622       INTEGER, DIMENSION(:), ALLOCATABLE ::  ira
623
624       LOGICAL, SAVE ::  first = .TRUE.
625
626       REAL ::  ek, particle_radius, pp, qq, rq
627
628       REAL, DIMENSION(1:21), SAVE ::  rat
629       REAL, DIMENSION(1:15), SAVE ::  r0
630       REAL, DIMENSION(1:15,1:21), SAVE ::  ecoll
631
632!
633!--    Initial assignment of constants
634       IF ( first )  THEN
635
636         first = .FALSE.
637         r0  = (/ 6.0, 8.0, 10.0, 15.0, 20.0, 25.0, 30.0, 40.0, 50.0, 60., &
638                  70.0, 100.0, 150.0, 200.0, 300.0 /)
639         rat = (/ 0.00, 0.05, 0.10, 0.15, 0.20, 0.25, 0.30, 0.35, 0.40, 0.45, &
640                  0.50, 0.55, 0.60, 0.65, 0.70, 0.75, 0.80, 0.85, 0.90, 0.95, &
641                  1.00 /)
642
643         ecoll(:,1) = (/0.001, 0.001, 0.001, 0.001, 0.001, 0.001, 0.001, &
644                        0.001, 0.001, 0.001, 0.001, 0.001, 0.001, 0.001, 0.001/)
645         ecoll(:,2) = (/0.003, 0.003, 0.003, 0.004, 0.005, 0.005, 0.005, &
646                        0.010, 0.100, 0.050, 0.200, 0.500, 0.770, 0.870, 0.970/)
647         ecoll(:,3) = (/0.007, 0.007, 0.007, 0.008, 0.009, 0.010, 0.010, &
648                        0.070, 0.400, 0.430, 0.580, 0.790, 0.930, 0.960, 1.000/)
649         ecoll(:,4) = (/0.009, 0.009, 0.009, 0.012, 0.015, 0.010, 0.020, &
650                        0.280, 0.600, 0.640, 0.750, 0.910, 0.970, 0.980, 1.000/)
651         ecoll(:,5) = (/0.014, 0.014, 0.014, 0.015, 0.016, 0.030, 0.060, &
652                        0.500, 0.700, 0.770, 0.840, 0.950, 0.970, 1.000, 1.000/)
653         ecoll(:,6) = (/0.017, 0.017, 0.017, 0.020, 0.022, 0.060, 0.100, &
654                        0.620, 0.780, 0.840, 0.880, 0.950, 1.000, 1.000, 1.000/)
655         ecoll(:,7) = (/0.030, 0.030, 0.024, 0.022, 0.032, 0.062, 0.200, &
656                        0.680, 0.830, 0.870, 0.900, 0.950, 1.000, 1.000, 1.000/)
657         ecoll(:,8) = (/0.025, 0.025, 0.025, 0.036, 0.043, 0.130, 0.270, &
658                        0.740, 0.860, 0.890, 0.920, 1.000, 1.000, 1.000, 1.000/)
659         ecoll(:,9) = (/0.027, 0.027, 0.027, 0.040, 0.052, 0.200, 0.400, &
660                        0.780, 0.880, 0.900, 0.940, 1.000, 1.000, 1.000, 1.000/)
661         ecoll(:,10)= (/0.030, 0.030, 0.030, 0.047, 0.064, 0.250, 0.500, &
662                        0.800, 0.900, 0.910, 0.950, 1.000, 1.000, 1.000, 1.000/)
663         ecoll(:,11)= (/0.040, 0.040, 0.033, 0.037, 0.068, 0.240, 0.550, &
664                        0.800, 0.900, 0.910, 0.950, 1.000, 1.000, 1.000, 1.000/)
665         ecoll(:,12)= (/0.035, 0.035, 0.035, 0.055, 0.079, 0.290, 0.580, &
666                        0.800, 0.900, 0.910, 0.950, 1.000, 1.000, 1.000, 1.000/)
667         ecoll(:,13)= (/0.037, 0.037, 0.037, 0.062, 0.082, 0.290, 0.590, &
668                        0.780, 0.900, 0.910, 0.950, 1.000, 1.000, 1.000, 1.000/)
669         ecoll(:,14)= (/0.037, 0.037, 0.037, 0.060, 0.080, 0.290, 0.580, &
670                        0.770, 0.890, 0.910, 0.950, 1.000, 1.000, 1.000, 1.000/)
671         ecoll(:,15)= (/0.037, 0.037, 0.037, 0.041, 0.075, 0.250, 0.540, &
672                        0.760, 0.880, 0.920, 0.950, 1.000, 1.000, 1.000, 1.000/)
673         ecoll(:,16)= (/0.037, 0.037, 0.037, 0.052, 0.067, 0.250, 0.510, &
674                        0.770, 0.880, 0.930, 0.970, 1.000, 1.000, 1.000, 1.000/)
675         ecoll(:,17)= (/0.037, 0.037, 0.037, 0.047, 0.057, 0.250, 0.490, &
676                        0.770, 0.890, 0.950, 1.000, 1.000, 1.000, 1.000, 1.000/)
677         ecoll(:,18)= (/0.036, 0.036, 0.036, 0.042, 0.048, 0.230, 0.470, &
678                        0.780, 0.920, 1.000, 1.020, 1.020, 1.020, 1.020, 1.020/)
679         ecoll(:,19)= (/0.040, 0.040, 0.035, 0.033, 0.040, 0.112, 0.450, &
680                        0.790, 1.010, 1.030, 1.040, 1.040, 1.040, 1.040, 1.040/)
681         ecoll(:,20)= (/0.033, 0.033, 0.033, 0.033, 0.033, 0.119, 0.470, &
682                        0.950, 1.300, 1.700, 2.300, 2.300, 2.300, 2.300, 2.300/)
683         ecoll(:,21)= (/0.027, 0.027, 0.027, 0.027, 0.027, 0.125, 0.520, &
684                        1.400, 2.300, 3.000, 4.000, 4.000, 4.000, 4.000, 4.000/)
685       ENDIF
686
687!
688!--    Calculate the radius class index of particles with respect to array r
689!--    Radius has to be in µm
690       ALLOCATE( ira(1:radius_classes) )
691       DO  j = 1, radius_classes
692          particle_radius = radclass(j) * 1.0E6
693          DO  k = 1, 15
694             IF ( particle_radius < r0(k) )  THEN
695                ira(j) = k
696                EXIT
697             ENDIF
698          ENDDO
699          IF ( particle_radius >= r0(15) )  ira(j) = 16
700       ENDDO
701
702!
703!--    Two-dimensional linear interpolation of the collision efficiency.
704!--    Radius has to be in µm
705       DO  j = 1, radius_classes
706          DO  i = 1, j
707
708             ir = ira(j)
709             rq = radclass(i) / radclass(j)
710             iq = INT( rq * 20 ) + 1
711             iq = MAX( iq , 2)
712
713             IF ( ir < 16 )  THEN
714                IF ( ir >= 2 )  THEN
715                   pp = ( ( radclass(j) * 1.0E06 ) - r0(ir-1) ) / &
716                        ( r0(ir) - r0(ir-1) )
717                   qq = ( rq- rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
718                   ec(j,i) = ( 1.0-pp ) * ( 1.0-qq ) * ecoll(ir-1,iq-1)  &
719                             + pp * ( 1.0-qq ) * ecoll(ir,iq-1)          &
720                             + qq * ( 1.0-pp ) * ecoll(ir-1,iq)          &
721                             + pp * qq * ecoll(ir,iq)
722                ELSE
723                   qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
724                   ec(j,i) = (1.0-qq) * ecoll(1,iq-1) + qq * ecoll(1,iq)
725                ENDIF
726             ELSE
727                qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
728                ek = ( 1.0 - qq ) * ecoll(15,iq-1) + qq * ecoll(15,iq)
729                ec(j,i) = MIN( ek, 1.0 )
730             ENDIF
731
732             IF ( ec(j,i) < 1.0E-20 )  ec(j,i) = 0.0
733
734             ec(i,j) = ec(j,i)
735
736          ENDDO
737       ENDDO
738
739       DEALLOCATE( ira )
740
741    END SUBROUTINE effic
742
743
744!------------------------------------------------------------------------------!
745! Calculation of enhancement factor for collision efficencies due to turbulence
746!------------------------------------------------------------------------------!
747    SUBROUTINE turb_enhance_eff
748
749       USE constants
750       USE cloud_parameters
751       USE particle_attributes
752       USE arrays_3d
753
754       IMPLICIT NONE
755
756       INTEGER :: i, ik, iq, ir, j, k, kk
757
758       INTEGER, DIMENSION(:), ALLOCATABLE ::  ira
759
760       REAL ::  particle_radius, pp, qq, rq, x1, x2, x3, y1, y2, y3
761
762       LOGICAL, SAVE ::  first = .TRUE.
763
764       REAL, DIMENSION(1:11), SAVE ::  rat
765       REAL, DIMENSION(1:7), SAVE  ::  r0
766       REAL, DIMENSION(1:7,1:11), SAVE ::  ecoll_100, ecoll_400
767
768!
769!--    Initial assignment of constants
770       IF ( first )  THEN
771
772          first = .FALSE.
773
774          r0  = (/ 10.0, 20.0, 30.0, 40.0, 50.0, 60.0, 100.0 /)
775          rat = (/ 0.0, 0.1, 0.2, 0.3, 0.4, 0.5, 0.6, 0.7, 0.8, 0.9, 1.0 /)
776!
777!--       for 100 cm**2/s**3
778          ecoll_100(:,1) = (/1.74,  1.74,  1.773, 1.49,  1.207,  1.207,  1.0 /)
779          ecoll_100(:,2) = (/1.46,  1.46,  1.421, 1.245, 1.069,  1.069,  1.0 /)
780          ecoll_100(:,3) = (/1.32,  1.32,  1.245, 1.123, 1.000,  1.000,  1.0 /)
781          ecoll_100(:,4) = (/1.250, 1.250, 1.148, 1.087, 1.025,  1.025,  1.0 /)
782          ecoll_100(:,5) = (/1.186, 1.186, 1.066, 1.060, 1.056,  1.056,  1.0 /)
783          ecoll_100(:,6) = (/1.045, 1.045, 1.000, 1.014, 1.028,  1.028,  1.0 /)
784          ecoll_100(:,7) = (/1.070, 1.070, 1.030, 1.038, 1.046,  1.046,  1.0 /)
785          ecoll_100(:,8) = (/1.000, 1.000, 1.054, 1.042, 1.029,  1.029,  1.0 /)
786          ecoll_100(:,9) = (/1.223, 1.223, 1.117, 1.069, 1.021,  1.021,  1.0 /)
787          ecoll_100(:,10)= (/1.570, 1.570, 1.244, 1.166, 1.088,  1.088,  1.0 /)
788          ecoll_100(:,11)= (/20.3,  20.3,  14.6 , 8.61,  2.60,   2.60 ,  1.0 /)
789!
790!--       for 400 cm**2/s**3
791          ecoll_400(:,1) = (/4.976, 4.976,  3.593, 2.519, 1.445,  1.445,  1.0 /)
792          ecoll_400(:,2) = (/2.984, 2.984,  2.181, 1.691, 1.201,  1.201,  1.0 /)
793          ecoll_400(:,3) = (/1.988, 1.988,  1.475, 1.313, 1.150,  1.150,  1.0 /)
794          ecoll_400(:,4) = (/1.490, 1.490,  1.187, 1.156, 1.126,  1.126,  1.0 /)
795          ecoll_400(:,5) = (/1.249, 1.249,  1.088, 1.090, 1.092,  1.092,  1.0 /)
796          ecoll_400(:,6) = (/1.139, 1.139,  1.130, 1.091, 1.051,  1.051,  1.0 /)
797          ecoll_400(:,7) = (/1.220, 1.220,  1.190, 1.138, 1.086,  1.086,  1.0 /)
798          ecoll_400(:,8) = (/1.325, 1.325,  1.267, 1.165, 1.063,  1.063,  1.0 /)
799          ecoll_400(:,9) = (/1.716, 1.716,  1.345, 1.223, 1.100,  1.100,  1.0 /)
800          ecoll_400(:,10)= (/3.788, 3.788,  1.501, 1.311, 1.120,  1.120,  1.0 /)
801          ecoll_400(:,11)= (/36.52, 36.52,  19.16, 22.80,  26.0,   26.0,  1.0 /)
802
803       ENDIF
804
805!
806!--    Calculate the radius class index of particles with respect to array r0
807!--    Radius has to be in µm
808       ALLOCATE( ira(1:radius_classes) )
809
810       DO  j = 1, radius_classes
811          particle_radius = radclass(j) * 1.0E6
812          DO  k = 1, 7
813             IF ( particle_radius < r0(k) )  THEN
814                ira(j) = k
815                EXIT
816             ENDIF
817          ENDDO
818          IF ( particle_radius >= r0(7) )  ira(j) = 8
819       ENDDO
820
821!
822!--    Two-dimensional linear interpolation of the collision efficiencies
823!--    Radius has to be in µm
824       DO  j =  1, radius_classes
825          DO  i = 1, j
826
827             ir = ira(j)
828             rq = radclass(i) / radclass(j)
829
830             DO  kk = 2, 11
831                IF ( rq <= rat(kk) )  THEN
832                   iq = kk
833                   EXIT
834                ENDIF
835             ENDDO
836
837             y1 = 0.0001      ! for 0 m**2/s**3
838
839             IF ( ir < 8 )  THEN
840                IF ( ir >= 2 )  THEN
841                   pp = ( radclass(j)*1.0E6 - r0(ir-1) ) / ( r0(ir) - r0(ir-1) )
842                   qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
843                   y2 = ( 1.0-pp ) * ( 1.0-qq ) * ecoll_100(ir-1,iq-1) +  &
844                                pp * ( 1.0-qq ) * ecoll_100(ir,iq-1)   +  &
845                                qq * ( 1.0-pp ) * ecoll_100(ir-1,iq)   +  &
846                                pp * qq         * ecoll_100(ir,iq)
847                   y3 = ( 1.0-pp ) * ( 1.0-qq ) * ecoll_400(ir-1,iq-1) +  &
848                                pp * ( 1.0-qq ) * ecoll_400(ir,iq-1)   +  &
849                                qq * ( 1.0-pp ) * ecoll_400(ir-1,iq)   +  &
850                                pp * qq         * ecoll_400(ir,iq)
851                ELSE
852                   qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
853                   y2 = ( 1.0-qq ) * ecoll_100(1,iq-1) + qq * ecoll_100(1,iq)
854                   y3 = ( 1.0-qq ) * ecoll_400(1,iq-1) + qq * ecoll_400(1,iq)
855                ENDIF
856             ELSE
857                qq = ( rq - rat(iq-1) ) / ( rat(iq) - rat(iq-1) )
858                y2 = ( 1.0-qq ) * ecoll_100(7,iq-1) + qq * ecoll_100(7,iq)
859                y3 = ( 1.0-qq ) * ecoll_400(7,iq-1) + qq * ecoll_400(7,iq)
860             ENDIF
861!
862!--          Linear interpolation of dissipation rate in m**2/s**3
863             IF ( epsilon <= 0.01 )  THEN
864                ecf(j,i) = ( epsilon - 0.01 ) / (   0.0 - 0.01 ) * y1 &
865                         + ( epsilon -   0.0 ) / ( 0.01 -   0.0 ) * y2
866             ELSEIF ( epsilon <= 0.06 )  THEN
867                ecf(j,i) = ( epsilon - 0.04 ) / ( 0.01 - 0.04 ) * y2 &
868                         + ( epsilon - 0.01 ) / ( 0.04 - 0.01 ) * y3
869             ELSE
870                ecf(j,i) = (   0.06 - 0.04 ) / ( 0.01 - 0.04 ) * y2 &
871                         + (   0.06 - 0.01 ) / ( 0.04 - 0.01 ) * y3
872             ENDIF
873
874             IF ( ecf(j,i) < 1.0 )  ecf(j,i) = 1.0
875
876             ecf(i,j) = ecf(j,i)
877
878          ENDDO
879       ENDDO
880
881    END SUBROUTINE turb_enhance_eff
882
883
884
885    SUBROUTINE collision_efficiency_rogers( mean_r, r, e)
886!------------------------------------------------------------------------------!
887! Collision efficiencies from table 8.2 in Rogers and Yau (1989, 3rd edition).
888! Values are calculated from table by bilinear interpolation.
889!------------------------------------------------------------------------------!
890
891       IMPLICIT NONE
892
893       INTEGER       ::  i, j, k
894
895       LOGICAL, SAVE ::  first = .TRUE.
896
897       REAL          ::  aa, bb, cc, dd, dx, dy, e, gg, mean_r, mean_rm, r, &
898                         rm, x, y
899
900       REAL, DIMENSION(1:9), SAVE      ::  collected_r = 0.0
901       REAL, DIMENSION(1:19), SAVE     ::  collector_r = 0.0
902       REAL, DIMENSION(1:9,1:19), SAVE ::  ef = 0.0
903
904       mean_rm = mean_r * 1.0E06
905       rm      = r      * 1.0E06
906
907       IF ( first )  THEN
908
909          collected_r = (/ 2.0, 3.0, 4.0, 6.0, 8.0, 10.0, 15.0, 20.0, 25.0 /)
910          collector_r = (/ 10.0, 20.0, 30.0, 40.0, 50.0, 60.0, 80.0, 100.0,  &
911                           150.0, 200.0, 300.0, 400.0, 500.0, 600.0, 1000.0, &
912                           1400.0, 1800.0, 2400.0, 3000.0 /)
913
914          ef(:,1) = (/0.017, 0.027, 0.037, 0.052, 0.052, 0.052, 0.052, 0.0, &
915                      0.0 /)
916          ef(:,2) = (/0.001, 0.016, 0.027, 0.060, 0.12, 0.17, 0.17, 0.17, 0.0 /)
917          ef(:,3) = (/0.001, 0.001, 0.02,  0.13,  0.28, 0.37, 0.54, 0.55, 0.47/)
918          ef(:,4) = (/0.001, 0.001, 0.02,  0.23,  0.4,  0.55, 0.7,  0.75, 0.75/)
919          ef(:,5) = (/0.01,  0.01,  0.03,  0.3,   0.4,  0.58, 0.73, 0.75, 0.79/)
920          ef(:,6) = (/0.01,  0.01,  0.13,  0.38,  0.57, 0.68, 0.80, 0.86, 0.91/)
921          ef(:,7) = (/0.01,  0.085, 0.23,  0.52,  0.68, 0.76, 0.86, 0.92, 0.95/)
922          ef(:,8) = (/0.01,  0.14,  0.32,  0.60,  0.73, 0.81, 0.90, 0.94, 0.96/)
923          ef(:,9) = (/0.025, 0.25,  0.43,  0.66,  0.78, 0.83, 0.92, 0.95, 0.96/)
924          ef(:,10)= (/0.039, 0.3,   0.46,  0.69,  0.81, 0.87, 0.93, 0.95, 0.96/)
925          ef(:,11)= (/0.095, 0.33,  0.51,  0.72,  0.82, 0.87, 0.93, 0.96, 0.97/)
926          ef(:,12)= (/0.098, 0.36,  0.51,  0.73,  0.83, 0.88, 0.93, 0.96, 0.97/)
927          ef(:,13)= (/0.1,   0.36,  0.52,  0.74,  0.83, 0.88, 0.93, 0.96, 0.97/)
928          ef(:,14)= (/0.17,  0.4,   0.54,  0.72,  0.83, 0.88, 0.94, 0.98, 1.0 /)
929          ef(:,15)= (/0.15,  0.37,  0.52,  0.74,  0.82, 0.88, 0.94, 0.98, 1.0 /)
930          ef(:,16)= (/0.11,  0.34,  0.49,  0.71,  0.83, 0.88, 0.94, 0.95, 1.0 /)
931          ef(:,17)= (/0.08,  0.29,  0.45,  0.68,  0.8,  0.86, 0.96, 0.94, 1.0 /)
932          ef(:,18)= (/0.04,  0.22,  0.39,  0.62,  0.75, 0.83, 0.92, 0.96, 1.0 /)
933          ef(:,19)= (/0.02,  0.16,  0.33,  0.55,  0.71, 0.81, 0.90, 0.94, 1.0 /)
934
935       ENDIF
936
937       DO  k = 1, 8
938          IF ( collected_r(k) <= mean_rm )  i = k
939       ENDDO
940
941       DO  k = 1, 18
942          IF ( collector_r(k) <= rm )  j = k
943       ENDDO
944
945       IF ( rm < 10.0 )  THEN
946          e = 0.0
947       ELSEIF ( mean_rm < 2.0 )  THEN
948          e = 0.001
949       ELSEIF ( mean_rm >= 25.0 )  THEN
950          IF( j <= 2 )  e = 0.0
951          IF( j == 3 )  e = 0.47
952          IF( j == 4 )  e = 0.8
953          IF( j == 5 )  e = 0.9
954          IF( j >=6  )  e = 1.0
955       ELSEIF ( rm >= 3000.0 )  THEN
956          IF( i == 1 )  e = 0.02
957          IF( i == 2 )  e = 0.16
958          IF( i == 3 )  e = 0.33
959          IF( i == 4 )  e = 0.55
960          IF( i == 5 )  e = 0.71
961          IF( i == 6 )  e = 0.81
962          IF( i == 7 )  e = 0.90
963          IF( i >= 8 )  e = 0.94
964       ELSE
965          x  = mean_rm - collected_r(i)
966          y  = rm - collector_r(j)
967          dx = collected_r(i+1) - collected_r(i)
968          dy = collector_r(j+1) - collector_r(j)
969          aa = x**2 + y**2
970          bb = ( dx - x )**2 + y**2
971          cc = x**2 + ( dy - y )**2
972          dd = ( dx - x )**2 + ( dy - y )**2
973          gg = aa + bb + cc + dd
974
975          e = ( (gg-aa)*ef(i,j) + (gg-bb)*ef(i+1,j) + (gg-cc)*ef(i,j+1) + &
976                (gg-dd)*ef(i+1,j+1) ) / (3.0*gg)
977       ENDIF
978
979    END SUBROUTINE collision_efficiency_rogers
980
981 END MODULE lpm_collision_kernels_mod
Note: See TracBrowser for help on using the repository browser.