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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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