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

Last change on this file since 1359 was 1359, checked in by hoffmann, 10 years ago

new Lagrangian particle structure integrated

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