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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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