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

Last change on this file since 3654 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 5.2 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-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: lpm_merging.f90 3241 2018-09-12 15:02:00Z suehring $
27! unused variables removed
28!
29! 2718 2018-01-02 08:49:38Z maronga
30! Corrected "Former revisions" section
31! Change in file header (GPL part)
32! Added comments
33!
34! 2263 2017-06-08 14:59:01Z schwenkel
35! Initial revision
36!
37!
38! Description:
39! ------------
40! This routine is a part of the Lagrangian particle model. Two Super droplets
41! which fulfill certain criterion's (e.g. a big weighting factor and a small
42! radius) can be merged into one super droplet with a increased number of
43! represented particles of the super droplet. This mechanism ensures an
44! improved a feasible amount of computational costs. The limits of particle
45! creation should be chosen carefully! The idea of this algorithm is based on
46! Unterstrasser and Soelch, 2014.
47!------------------------------------------------------------------------------!
48 SUBROUTINE lpm_merging
49
50
51    USE arrays_3d,                                                             &
52        ONLY:  ql
53
54    USE cpulog,                                                                &
55        ONLY:  cpu_log, log_point_s
56
57    USE indices,                                                               &
58        ONLY:  nxl, nxr, nyn, nys, nzb, nzt
59
60    USE kinds
61
62    USE particle_attributes,                                                   &
63        ONLY:  deleted_particles, grid_particles, initial_weighting_factor,    &     
64               merge_drp, number_of_particles, particles, prt_count,           &
65               radius_merge, sum_merge_drp, weight_factor_merge
66
67    USE pegrid
68
69    IMPLICIT NONE
70
71    INTEGER(iwp) ::  i         !<     
72    INTEGER(iwp) ::  j         !<       
73    INTEGER(iwp) ::  k         !<       
74    INTEGER(iwp) ::  n         !<   
75   
76    REAL(wp) ::  ql_crit = 1.0E-5_wp  !< threshold lwc for cloudy grid cells
77                                      !< (e.g. Siebesma et al 2003, JAS, 60)
78   
79    CALL cpu_log( log_point_s(81), 'lpm_merging', 'start' )
80
81    merge_drp  = 0
82   
83    IF ( weight_factor_merge == -1.0_wp )  THEN
84       weight_factor_merge = 0.5_wp * initial_weighting_factor 
85    ENDIF
86
87    DO  i = nxl, nxr
88       DO  j = nys, nyn
89          DO  k = nzb+1, nzt
90   
91             number_of_particles = prt_count(k,j,i)
92             IF ( number_of_particles <= 0  .OR.                               &
93                   ql(k,j,i) >= ql_crit )  CYCLE
94             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
95!
96!--          Start merging operations: This routine delete super droplets with
97!--          a small radius (radius <= radius_merge) and a low weighting
98!--          factor (weight_factor  <= weight_factor_merge). The number of
99!--          represented particles will be added to the next particle of the
100!--          particle array. Tests showed that this simplified method can be
101!--          used because it will only take place outside of cloudy grid
102!--          boxes where ql <= 1.0E-5 kg/kg. Therefore, especially former cloned   
103!--          and subsequent evaporated super droplets will be merged.
104             DO  n = 1, number_of_particles-1
105                IF ( particles(n)%particle_mask                    .AND.       &
106                     particles(n+1)%particle_mask                  .AND.       &
107                     particles(n)%radius        <= radius_merge    .AND.       &
108                     particles(n)%weight_factor <= weight_factor_merge )       &   
109                THEN
110                   particles(n+1)%weight_factor  =                             &
111                                       particles(n+1)%weight_factor +          &
112                                       ( particles(n)%radius**3     /          &
113                                         particles(n+1)%radius**3   *          &
114                                         particles(n)%weight_factor            &
115                                       )
116                   particles(n)%particle_mask = .FALSE.
117                   deleted_particles          = deleted_particles + 1 
118                   merge_drp                  = merge_drp + 1
119               
120                ENDIF
121             ENDDO
122          ENDDO
123       ENDDO
124    ENDDO
125       
126    sum_merge_drp = sum_merge_drp + merge_drp
127
128    CALL cpu_log( log_point_s(81), 'lpm_merging', 'stop' )
129
130 END SUBROUTINE lpm_merging
Note: See TracBrowser for help on using the repository browser.