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

Last change on this file since 1347 was 1347, checked in by heinze, 10 years ago

last commit documented

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