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

Last change on this file since 1929 was 1929, checked in by suehring, 8 years ago

several bugfixes in particle model and serial mode

  • Property svn:keywords set to Id
File size: 9.4 KB
RevLine 
[1682]1!> @file lpm_init_sgs_tke.f90
[1036]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1818]16! Copyright 1997-2016 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[849]19! Current revisions:
20! ------------------
[1929]21! sgs_wfu_par, sgs_wfv_par and sgs_wfw_par are replaced by sgs_wf_par
[1360]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: lpm_init_sgs_tke.f90 1929 2016-06-09 16:25:25Z suehring $
26!
[1823]27! 1822 2016-04-07 07:49:42Z hoffmann
28! Unused variables removed.
29!
[1683]30! 1682 2015-10-07 23:56:08Z knoop
31! Code annotations made doxygen readable
32!
[1360]33! 1359 2014-04-11 17:15:14Z hoffmann
34! New particle structure integrated.
35! Kind definition added to all floating point numbers.
36!
[1321]37! 1320 2014-03-20 08:40:49Z raasch
[1320]38! ONLY-attribute added to USE-statements,
39! kind-parameters added to all INTEGER and REAL declaration statements,
40! kinds are defined in new module kinds,
41! comment fields (!:) to be used for variable explanations added to
42! all variable declaration statements
[849]43!
[1037]44! 1036 2012-10-22 13:43:42Z raasch
45! code put under GPL (PALM 3.9)
46!
[850]47! 849 2012-03-15 10:35:09Z raasch
48! initial revision (former part of advec_particles)
[849]49!
[850]50!
[849]51! Description:
52! ------------
[1682]53!> Calculates quantities required for considering the SGS velocity fluctuations
54!> in the particle transport by a stochastic approach. The respective
55!> quantities are: SGS-TKE gradients and horizontally averaged profiles of the
56!> SGS TKE and the resolved-scale velocity variances.
[849]57!------------------------------------------------------------------------------!
[1682]58 SUBROUTINE lpm_init_sgs_tke
59 
[849]60
[1320]61    USE arrays_3d,                                                             &
62        ONLY:  de_dx, de_dy, de_dz, diss, e, u, v, w, zu
63
64    USE grid_variables,                                                        &
65        ONLY:  ddx, ddy
66
67    USE indices,                                                               &
[1822]68        ONLY:  nbgp, ngp_2dh_outer, nxl, nxr, nyn, nys, nzb, nzb_s_inner,      &
69               nzb_s_outer, nzt
[1320]70
71    USE kinds
72
73    USE particle_attributes,                                                   &
[1929]74        ONLY:  sgs_wf_part
[1320]75
[849]76    USE pegrid
77
[1320]78    USE statistics,                                                            &
79        ONLY:  flow_statistics_called, hom, sums, sums_l
80
[849]81    IMPLICIT NONE
82
[1682]83    INTEGER(iwp) ::  i      !<
84    INTEGER(iwp) ::  j      !<
85    INTEGER(iwp) ::  k      !<
[849]86
87
88!
89!-- TKE gradient along x and y
90    DO  i = nxl, nxr
91       DO  j = nys, nyn
92          DO  k = nzb, nzt+1
93
94             IF ( k <= nzb_s_inner(j,i-1)  .AND.  k > nzb_s_inner(j,i)  .AND.  &
95                  k  > nzb_s_inner(j,i+1) )                                    &
96             THEN
[1929]97                de_dx(k,j,i) = 2.0_wp * sgs_wf_part *                          &
[1359]98                               ( e(k,j,i+1) - e(k,j,i) ) * ddx
[849]99             ELSEIF ( k  > nzb_s_inner(j,i-1)  .AND.  k > nzb_s_inner(j,i)     &
100                      .AND.  k <= nzb_s_inner(j,i+1) )                         &
101             THEN
[1929]102                de_dx(k,j,i) = 2.0_wp * sgs_wf_part *                          &
[1359]103                               ( e(k,j,i) - e(k,j,i-1) ) * ddx
[849]104             ELSEIF ( k < nzb_s_inner(j,i)  .AND.  k < nzb_s_inner(j,i+1) )    &
105             THEN
[1359]106                de_dx(k,j,i) = 0.0_wp
[849]107             ELSEIF ( k < nzb_s_inner(j,i-1)  .AND.  k < nzb_s_inner(j,i) )    &
108             THEN
[1359]109                de_dx(k,j,i) = 0.0_wp
[849]110             ELSE
[1929]111                de_dx(k,j,i) = sgs_wf_part * ( e(k,j,i+1) - e(k,j,i-1) ) * ddx
[849]112             ENDIF
113
114             IF ( k <= nzb_s_inner(j-1,i)  .AND.  k > nzb_s_inner(j,i)  .AND.  &
115                  k  > nzb_s_inner(j+1,i) )                                    &
116             THEN
[1929]117                de_dy(k,j,i) = 2.0_wp * sgs_wf_part *                          &
[1359]118                               ( e(k,j+1,i) - e(k,j,i) ) * ddy
[849]119             ELSEIF ( k  > nzb_s_inner(j-1,i)  .AND.  k  > nzb_s_inner(j,i)    &
120                      .AND.  k <= nzb_s_inner(j+1,i) )                         &
121             THEN
[1929]122                de_dy(k,j,i) = 2.0_wp * sgs_wf_part *                          &
[1359]123                               ( e(k,j,i) - e(k,j-1,i) ) * ddy
[849]124             ELSEIF ( k < nzb_s_inner(j,i)  .AND.  k < nzb_s_inner(j+1,i) )    &
125             THEN
[1359]126                de_dy(k,j,i) = 0.0_wp
[849]127             ELSEIF ( k < nzb_s_inner(j-1,i)  .AND.  k < nzb_s_inner(j,i) )    &
128             THEN
[1359]129                de_dy(k,j,i) = 0.0_wp
[849]130             ELSE
[1929]131                de_dy(k,j,i) = sgs_wf_part * ( e(k,j+1,i) - e(k,j-1,i) ) * ddy
[849]132             ENDIF
133
134          ENDDO
135       ENDDO
136    ENDDO
137
138!
139!-- TKE gradient along z, including bottom and top boundary conditions
140    DO  i = nxl, nxr
141       DO  j = nys, nyn
142
143          DO  k = nzb_s_inner(j,i)+2, nzt-1
[1929]144             de_dz(k,j,i)  = 2.0_wp * sgs_wf_part *                            &
[849]145                             ( e(k+1,j,i) - e(k-1,j,i) ) / ( zu(k+1)-zu(k-1) )
146          ENDDO
147
148          k = nzb_s_inner(j,i)
[1359]149          de_dz(nzb:k,j,i) = 0.0_wp
[1929]150          de_dz(k+1,j,i)   = 2.0_wp * sgs_wf_part *                            &
[1359]151                             ( e(k+2,j,i) - e(k+1,j,i) ) / ( zu(k+2) - zu(k+1) )
152          de_dz(nzt,j,i)   = 0.0_wp
153          de_dz(nzt+1,j,i) = 0.0_wp
[849]154       ENDDO
155    ENDDO
156
157
158!
159!-- Lateral boundary conditions
160    CALL exchange_horiz( de_dx, nbgp )
161    CALL exchange_horiz( de_dy, nbgp )
162    CALL exchange_horiz( de_dz, nbgp )
163    CALL exchange_horiz( diss, nbgp  )
164
165
166!
167!-- Calculate the horizontally averaged profiles of SGS TKE and resolved
168!-- velocity variances (they may have been already calculated in routine
169!-- flow_statistics).
170    IF ( .NOT. flow_statistics_called )  THEN
171
172!
173!--    First calculate horizontally averaged profiles of the horizontal
174!--    velocities.
[1359]175       sums_l(:,1,0) = 0.0_wp
176       sums_l(:,2,0) = 0.0_wp
[849]177
178       DO  i = nxl, nxr
179          DO  j =  nys, nyn
180             DO  k = nzb_s_outer(j,i), nzt+1
181                sums_l(k,1,0)  = sums_l(k,1,0)  + u(k,j,i)
182                sums_l(k,2,0)  = sums_l(k,2,0)  + v(k,j,i)
183             ENDDO
184          ENDDO
185       ENDDO
186
187#if defined( __parallel )
188!
189!--    Compute total sum from local sums
190       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
191       CALL MPI_ALLREDUCE( sums_l(nzb,1,0), sums(nzb,1), nzt+2-nzb, &
192                           MPI_REAL, MPI_SUM, comm2d, ierr )
193       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
194       CALL MPI_ALLREDUCE( sums_l(nzb,2,0), sums(nzb,2), nzt+2-nzb, &
195                              MPI_REAL, MPI_SUM, comm2d, ierr )
196#else
197       sums(:,1) = sums_l(:,1,0)
198       sums(:,2) = sums_l(:,2,0)
199#endif
200
201!
202!--    Final values are obtained by division by the total number of grid
203!--    points used for the summation.
204       hom(:,1,1,0) = sums(:,1) / ngp_2dh_outer(:,0)   ! u
205       hom(:,1,2,0) = sums(:,2) / ngp_2dh_outer(:,0)   ! v
206
207!
208!--    Now calculate the profiles of SGS TKE and the resolved-scale
209!--    velocity variances
[1359]210       sums_l(:,8,0)  = 0.0_wp
211       sums_l(:,30,0) = 0.0_wp
212       sums_l(:,31,0) = 0.0_wp
213       sums_l(:,32,0) = 0.0_wp
[849]214       DO  i = nxl, nxr
215          DO  j = nys, nyn
216             DO  k = nzb_s_outer(j,i), nzt+1
217                sums_l(k,8,0)  = sums_l(k,8,0)  + e(k,j,i)
218                sums_l(k,30,0) = sums_l(k,30,0) + ( u(k,j,i) - hom(k,1,1,0) )**2
219                sums_l(k,31,0) = sums_l(k,31,0) + ( v(k,j,i) - hom(k,1,2,0) )**2
220                sums_l(k,32,0) = sums_l(k,32,0) + w(k,j,i)**2
221             ENDDO
222          ENDDO
223       ENDDO
224
225#if defined( __parallel )
226!
227!--    Compute total sum from local sums
228       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
229       CALL MPI_ALLREDUCE( sums_l(nzb,8,0), sums(nzb,8), nzt+2-nzb, &
230                           MPI_REAL, MPI_SUM, comm2d, ierr )
231       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
232       CALL MPI_ALLREDUCE( sums_l(nzb,30,0), sums(nzb,30), nzt+2-nzb, &
233                           MPI_REAL, MPI_SUM, comm2d, ierr )
234       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
235       CALL MPI_ALLREDUCE( sums_l(nzb,31,0), sums(nzb,31), nzt+2-nzb, &
236                           MPI_REAL, MPI_SUM, comm2d, ierr )
237       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
238       CALL MPI_ALLREDUCE( sums_l(nzb,32,0), sums(nzb,32), nzt+2-nzb, &
239                           MPI_REAL, MPI_SUM, comm2d, ierr )
240
241#else
242       sums(:,8)  = sums_l(:,8,0)
243       sums(:,30) = sums_l(:,30,0)
244       sums(:,31) = sums_l(:,31,0)
245       sums(:,32) = sums_l(:,32,0)
246#endif
247
248!
249!--    Final values are obtained by division by the total number of grid
250!--    points used for the summation.
251       hom(:,1,8,0)  = sums(:,8)  / ngp_2dh_outer(:,0)   ! e
252       hom(:,1,30,0) = sums(:,30) / ngp_2dh_outer(:,0)   ! u*2
253       hom(:,1,31,0) = sums(:,31) / ngp_2dh_outer(:,0)   ! v*2
254       hom(:,1,32,0) = sums(:,32) / ngp_2dh_outer(:,0)   ! w*2
255
256    ENDIF
257
258 END SUBROUTINE lpm_init_sgs_tke
Note: See TracBrowser for help on using the repository browser.