source: palm/trunk/SOURCE/lpm_init_sgs_tke.f90 @ 1320

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 8.8 KB
Line 
1 SUBROUTINE lpm_init_sgs_tke
2
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!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22! ONLY-attribute added to USE-statements,
23! kind-parameters added to all INTEGER and REAL declaration statements,
24! kinds are defined in new module kinds,
25! comment fields (!:) to be used for variable explanations added to
26! all variable declaration statements
27!
28! Former revisions:
29! -----------------
30! $Id: lpm_init_sgs_tke.f90 1320 2014-03-20 08:40:49Z raasch $
31!
32! 1036 2012-10-22 13:43:42Z raasch
33! code put under GPL (PALM 3.9)
34!
35! 849 2012-03-15 10:35:09Z raasch
36! initial revision (former part of advec_particles)
37!
38!
39! Description:
40! ------------
41! Calculates quantities required for considering the SGS velocity fluctuations
42! in the particle transport by a stochastic approach. The respective
43! quantities are: SGS-TKE gradients and horizontally averaged profiles of the
44! SGS TKE and the resolved-scale velocity variances.
45!------------------------------------------------------------------------------!
46
47    USE arrays_3d,                                                             &
48        ONLY:  de_dx, de_dy, de_dz, diss, e, u, v, w, zu
49
50    USE grid_variables,                                                        &
51        ONLY:  ddx, ddy
52
53    USE indices,                                                               &
54        ONLY:  nbgp, ngp_2dh_outer, nx, nxl, nxr, ny, nyn, nys, nz, nzb,       &
55                      nzb_s_inner, nzb_s_outer, nzt
56
57    USE kinds
58
59    USE particle_attributes,                                                   &
60        ONLY:  sgs_wfu_part, sgs_wfv_part, sgs_wfw_part
61
62    USE pegrid
63
64    USE statistics,                                                            &
65        ONLY:  flow_statistics_called, hom, sums, sums_l
66
67    IMPLICIT NONE
68
69    INTEGER(iwp) ::  i      !:
70    INTEGER(iwp) ::  j      !:
71    INTEGER(iwp) ::  k      !:
72
73
74!
75!-- TKE gradient along x and y
76    DO  i = nxl, nxr
77       DO  j = nys, nyn
78          DO  k = nzb, nzt+1
79
80             IF ( k <= nzb_s_inner(j,i-1)  .AND.  k > nzb_s_inner(j,i)  .AND.  &
81                  k  > nzb_s_inner(j,i+1) )                                    &
82             THEN
83                de_dx(k,j,i) = 2.0 * sgs_wfu_part * ( e(k,j,i+1) - e(k,j,i) )  &
84                               * ddx
85             ELSEIF ( k  > nzb_s_inner(j,i-1)  .AND.  k > nzb_s_inner(j,i)     &
86                      .AND.  k <= nzb_s_inner(j,i+1) )                         &
87             THEN
88                de_dx(k,j,i) = 2.0 * sgs_wfu_part * ( e(k,j,i) - e(k,j,i-1) )  &
89                               * ddx
90             ELSEIF ( k < nzb_s_inner(j,i)  .AND.  k < nzb_s_inner(j,i+1) )    &
91             THEN
92                de_dx(k,j,i) = 0.0
93             ELSEIF ( k < nzb_s_inner(j,i-1)  .AND.  k < nzb_s_inner(j,i) )    &
94             THEN
95                de_dx(k,j,i) = 0.0
96             ELSE
97                de_dx(k,j,i) = sgs_wfu_part * ( e(k,j,i+1) - e(k,j,i-1) ) * ddx
98             ENDIF
99
100             IF ( k <= nzb_s_inner(j-1,i)  .AND.  k > nzb_s_inner(j,i)  .AND.  &
101                  k  > nzb_s_inner(j+1,i) )                                    &
102             THEN
103                de_dy(k,j,i) = 2.0 * sgs_wfv_part * ( e(k,j+1,i) - e(k,j,i) )  &
104                               * ddy
105             ELSEIF ( k  > nzb_s_inner(j-1,i)  .AND.  k  > nzb_s_inner(j,i)    &
106                      .AND.  k <= nzb_s_inner(j+1,i) )                         &
107             THEN
108                de_dy(k,j,i) = 2.0 * sgs_wfv_part * ( e(k,j,i) - e(k,j-1,i) )  &
109                               * ddy
110             ELSEIF ( k < nzb_s_inner(j,i)  .AND.  k < nzb_s_inner(j+1,i) )    &
111             THEN
112                de_dy(k,j,i) = 0.0
113             ELSEIF ( k < nzb_s_inner(j-1,i)  .AND.  k < nzb_s_inner(j,i) )    &
114             THEN
115                de_dy(k,j,i) = 0.0
116             ELSE
117                de_dy(k,j,i) = sgs_wfv_part * ( e(k,j+1,i) - e(k,j-1,i) ) * ddy
118             ENDIF
119
120          ENDDO
121       ENDDO
122    ENDDO
123
124!
125!-- TKE gradient along z, including bottom and top boundary conditions
126    DO  i = nxl, nxr
127       DO  j = nys, nyn
128
129          DO  k = nzb_s_inner(j,i)+2, nzt-1
130             de_dz(k,j,i)  = 2.0 * sgs_wfw_part * &
131                             ( e(k+1,j,i) - e(k-1,j,i) ) / ( zu(k+1)-zu(k-1) )
132          ENDDO
133
134          k = nzb_s_inner(j,i)
135          de_dz(nzb:k,j,i) = 0.0
136          de_dz(k+1,j,i)   = 2.0 * sgs_wfw_part * ( e(k+2,j,i) - e(k+1,j,i) ) &
137                                                / ( zu(k+2) - zu(k+1) )
138          de_dz(nzt,j,i)   = 0.0
139          de_dz(nzt+1,j,i) = 0.0
140       ENDDO
141    ENDDO
142
143
144!
145!-- Lateral boundary conditions
146    CALL exchange_horiz( de_dx, nbgp )
147    CALL exchange_horiz( de_dy, nbgp )
148    CALL exchange_horiz( de_dz, nbgp )
149    CALL exchange_horiz( diss, nbgp  )
150
151
152!
153!-- Calculate the horizontally averaged profiles of SGS TKE and resolved
154!-- velocity variances (they may have been already calculated in routine
155!-- flow_statistics).
156    IF ( .NOT. flow_statistics_called )  THEN
157
158!
159!--    First calculate horizontally averaged profiles of the horizontal
160!--    velocities.
161       sums_l(:,1,0) = 0.0
162       sums_l(:,2,0) = 0.0
163
164       DO  i = nxl, nxr
165          DO  j =  nys, nyn
166             DO  k = nzb_s_outer(j,i), nzt+1
167                sums_l(k,1,0)  = sums_l(k,1,0)  + u(k,j,i)
168                sums_l(k,2,0)  = sums_l(k,2,0)  + v(k,j,i)
169             ENDDO
170          ENDDO
171       ENDDO
172
173#if defined( __parallel )
174!
175!--    Compute total sum from local sums
176       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
177       CALL MPI_ALLREDUCE( sums_l(nzb,1,0), sums(nzb,1), nzt+2-nzb, &
178                           MPI_REAL, MPI_SUM, comm2d, ierr )
179       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
180       CALL MPI_ALLREDUCE( sums_l(nzb,2,0), sums(nzb,2), nzt+2-nzb, &
181                              MPI_REAL, MPI_SUM, comm2d, ierr )
182#else
183       sums(:,1) = sums_l(:,1,0)
184       sums(:,2) = sums_l(:,2,0)
185#endif
186
187!
188!--    Final values are obtained by division by the total number of grid
189!--    points used for the summation.
190       hom(:,1,1,0) = sums(:,1) / ngp_2dh_outer(:,0)   ! u
191       hom(:,1,2,0) = sums(:,2) / ngp_2dh_outer(:,0)   ! v
192
193!
194!--    Now calculate the profiles of SGS TKE and the resolved-scale
195!--    velocity variances
196       sums_l(:,8,0)  = 0.0
197       sums_l(:,30,0) = 0.0
198       sums_l(:,31,0) = 0.0
199       sums_l(:,32,0) = 0.0
200       DO  i = nxl, nxr
201          DO  j = nys, nyn
202             DO  k = nzb_s_outer(j,i), nzt+1
203                sums_l(k,8,0)  = sums_l(k,8,0)  + e(k,j,i)
204                sums_l(k,30,0) = sums_l(k,30,0) + ( u(k,j,i) - hom(k,1,1,0) )**2
205                sums_l(k,31,0) = sums_l(k,31,0) + ( v(k,j,i) - hom(k,1,2,0) )**2
206                sums_l(k,32,0) = sums_l(k,32,0) + w(k,j,i)**2
207             ENDDO
208          ENDDO
209       ENDDO
210
211#if defined( __parallel )
212!
213!--    Compute total sum from local sums
214       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
215       CALL MPI_ALLREDUCE( sums_l(nzb,8,0), sums(nzb,8), nzt+2-nzb, &
216                           MPI_REAL, MPI_SUM, comm2d, ierr )
217       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
218       CALL MPI_ALLREDUCE( sums_l(nzb,30,0), sums(nzb,30), nzt+2-nzb, &
219                           MPI_REAL, MPI_SUM, comm2d, ierr )
220       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
221       CALL MPI_ALLREDUCE( sums_l(nzb,31,0), sums(nzb,31), nzt+2-nzb, &
222                           MPI_REAL, MPI_SUM, comm2d, ierr )
223       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
224       CALL MPI_ALLREDUCE( sums_l(nzb,32,0), sums(nzb,32), nzt+2-nzb, &
225                           MPI_REAL, MPI_SUM, comm2d, ierr )
226
227#else
228       sums(:,8)  = sums_l(:,8,0)
229       sums(:,30) = sums_l(:,30,0)
230       sums(:,31) = sums_l(:,31,0)
231       sums(:,32) = sums_l(:,32,0)
232#endif
233
234!
235!--    Final values are obtained by division by the total number of grid
236!--    points used for the summation.
237       hom(:,1,8,0)  = sums(:,8)  / ngp_2dh_outer(:,0)   ! e
238       hom(:,1,30,0) = sums(:,30) / ngp_2dh_outer(:,0)   ! u*2
239       hom(:,1,31,0) = sums(:,31) / ngp_2dh_outer(:,0)   ! v*2
240       hom(:,1,32,0) = sums(:,32) / ngp_2dh_outer(:,0)   ! w*2
241
242    ENDIF
243
244 END SUBROUTINE lpm_init_sgs_tke
Note: See TracBrowser for help on using the repository browser.