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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

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