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

Last change on this file since 1310 was 1310, checked in by raasch, 10 years ago

update of GPL copyright

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