source: palm/trunk/SOURCE/lpm_merging.f90 @ 2292

Last change on this file since 2292 was 2278, checked in by schwenkel, 7 years ago

Added comments

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 5.0 KB
Line 
1!> @file lpm_merging.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26!
27! Added comments
28!
29!
30! 2263 2017-06-08 14:59:01Z schwenkel
31! Initial revision
32!
33!
34!
35! Description:
36! ------------
37! This routine is a part of the Lagrangian particle model. Two Super droplets
38! which fulfill certain criterion's (e.g. a big weighting factor and a small
39! radius) can be merged into one super droplet with a increased number of
40! represented particles of the super droplet. This mechanism ensures an
41! improved a feasible amount of computational costs. The limits of particle
42! creation should be chosen carefully! The idea of this algorithm is based on
43! Unterstrasser and Soelch, 2014.
44!------------------------------------------------------------------------------!
45 SUBROUTINE lpm_merging
46
47
48    USE arrays_3d,                                                             &
49        ONLY:  ql
50
51    USE cpulog,                                                                &
52        ONLY:  cpu_log, log_point_s
53
54    USE indices,                                                               &
55        ONLY:  nxl, nxr, nyn, nys, nzb, nzt
56
57    USE kinds
58
59    USE particle_attributes,                                                   &
60        ONLY:  deleted_particles, grid_particles, initial_weighting_factor,    &     
61               merge_drp, merging, number_of_particles, particles, prt_count,  &
62               radius_merge, sum_merge_drp, weight_factor_merge
63
64    USE pegrid
65
66    IMPLICIT NONE
67
68    INTEGER(iwp) ::  i         !<     
69    INTEGER(iwp) ::  j         !<       
70    INTEGER(iwp) ::  k         !<       
71    INTEGER(iwp) ::  n         !<   
72   
73    REAL(wp) ::  ql_crit = 1.0E-5_wp  !< threshold lwc for cloudy grid cells
74                                      !< (e.g. Siebesma et al 2003, JAS, 60)
75   
76    CALL cpu_log( log_point_s(81), 'lpm_merging', 'start' )
77
78    merge_drp  = 0
79   
80    IF ( weight_factor_merge == -1.0_wp )  THEN
81       weight_factor_merge = 0.5_wp * initial_weighting_factor 
82    ENDIF
83
84    DO  i = nxl, nxr
85       DO  j = nys, nyn
86          DO  k = nzb+1, nzt
87   
88             number_of_particles = prt_count(k,j,i)
89             IF ( number_of_particles <= 0  .OR.                               &
90                   ql(k,j,i) >= ql_crit )  CYCLE
91             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
92!
93!--          Start merging operations: This routine delete super droplets with
94!--          a small radius (radius <= radius_merge) and a low weighting
95!--          factor (weight_factor  <= weight_factor_merge). The number of
96!--          represented particles will be added to the next particle of the
97!--          particle array. Tests showed that this simplified method can be
98!--          used because it will only take place outside of cloudy grid
99!--          boxes where ql <= 1.0E-5 kg/kg. Therefore, especially former cloned   
100!--          and subsequent evaporated super droplets will be merged.
101             DO  n = 1, number_of_particles-1
102                IF ( particles(n)%particle_mask                    .AND.       &
103                     particles(n+1)%particle_mask                  .AND.       &
104                     particles(n)%radius        <= radius_merge    .AND.       &
105                     particles(n)%weight_factor <= weight_factor_merge )       &   
106                THEN
107                   particles(n+1)%weight_factor  =                             &
108                                       particles(n+1)%weight_factor +          &
109                                       ( particles(n)%radius**3     /          &
110                                         particles(n+1)%radius**3   *          &
111                                         particles(n)%weight_factor            &
112                                       )
113                   particles(n)%particle_mask = .FALSE.
114                   deleted_particles          = deleted_particles + 1 
115                   merge_drp                  = merge_drp + 1
116               
117                ENDIF
118             ENDDO
119          ENDDO
120       ENDDO
121    ENDDO
122       
123    sum_merge_drp = sum_merge_drp + merge_drp
124
125    CALL cpu_log( log_point_s(81), 'lpm_merging', 'stop' )
126
127 END SUBROUTINE lpm_merging
Note: See TracBrowser for help on using the repository browser.