source: palm/trunk/SOURCE/inflow_turbulence.f90 @ 1322

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

last commit documented

  • Property svn:keywords set to Id
File size: 6.9 KB
Line 
1 SUBROUTINE inflow_turbulence
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!
23!
24! module interfaces removed
25!
26! Former revisions:
27! -----------------
28! $Id: inflow_turbulence.f90 1321 2014-03-20 09:40:40Z raasch $
29!
30! 1320 2014-03-20 08:40:49Z raasch
31! ONLY-attribute added to USE-statements,
32! kind-parameters added to all INTEGER and REAL declaration statements,
33! kinds are defined in new module kinds,
34! revision history before 2012 removed,
35! comment fields (!:) to be used for variable explanations added to
36! all variable declaration statements
37!
38! 1092 2013-02-02 11:24:22Z raasch
39! unused variables removed
40!
41! 1036 2012-10-22 13:43:42Z raasch
42! code put under GPL (PALM 3.9)
43!
44! Initial version (2008/03/07)
45!
46! Description:
47! ------------
48! Imposing turbulence at the respective inflow using the turbulence
49! recycling method of Kataoka and Mizuno (2002).
50!------------------------------------------------------------------------------!
51
52    USE arrays_3d,                                                             &
53        ONLY:  e, inflow_damping_factor, mean_inflow_profiles, pt, u, v, w
54       
55    USE control_parameters,                                                    &
56        ONLY:  recycling_plane
57       
58    USE cpulog,                                                                &
59        ONLY:  cpu_log, log_point
60       
61    USE grid_variables,                                                        &
62        ONLY: 
63       
64    USE indices,                                                               &
65        ONLY:  nbgp, nxl, ny, nyn, nys, nyng, nysg, nzb, nzt
66       
67    USE kinds
68   
69    USE pegrid
70
71
72    IMPLICIT NONE
73
74    INTEGER(iwp) ::  i        !:
75    INTEGER(iwp) ::  j        !:
76    INTEGER(iwp) ::  k        !:
77    INTEGER(iwp) ::  l        !:
78    INTEGER(iwp) ::  ngp_ifd  !:
79    INTEGER(iwp) ::  ngp_pr   !:
80
81    REAL(wp), DIMENSION(nzb:nzt+1,5,nbgp)           ::                         &
82       avpr, avpr_l  !:
83    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,5,nbgp) ::                         &
84       inflow_dist   !:
85
86    CALL cpu_log( log_point(40), 'inflow_turbulence', 'start' )
87
88!
89!-- Carry out spanwise averaging in the recycling plane
90    avpr_l = 0.0
91    ngp_pr = ( nzt - nzb + 2 ) * 5 * nbgp
92    ngp_ifd = ngp_pr * ( nyn - nys + 1 + 2 * nbgp )
93
94!
95!-- First, local averaging within the recycling domain
96    i = recycling_plane
97
98#if defined( __parallel )
99    IF ( myidx == id_recycling )  THEN
100       
101       DO  l = 1, nbgp
102          DO  j = nys, nyn
103             DO  k = nzb, nzt + 1
104
105                avpr_l(k,1,l) = avpr_l(k,1,l) + u(k,j,i)
106                avpr_l(k,2,l) = avpr_l(k,2,l) + v(k,j,i)
107                avpr_l(k,3,l) = avpr_l(k,3,l) + w(k,j,i)
108                avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i)
109                avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i)
110
111             ENDDO
112          ENDDO
113          i = i + 1
114       ENDDO
115
116    ENDIF
117!
118!-- Now, averaging over all PEs
119    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
120    CALL MPI_ALLREDUCE( avpr_l(nzb,1,1), avpr(nzb,1,1), ngp_pr, MPI_REAL, &
121                        MPI_SUM, comm2d, ierr )
122
123#else
124    DO  l = 1, nbgp
125       DO  j = nys, nyn
126          DO  k = nzb, nzt + 1
127
128             avpr_l(k,1,l) = avpr_l(k,1,l) + u(k,j,i)
129             avpr_l(k,2,l) = avpr_l(k,2,l) + v(k,j,i)
130             avpr_l(k,3,l) = avpr_l(k,3,l) + w(k,j,i)
131             avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i)
132             avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i)
133
134          ENDDO
135       ENDDO
136       i = i + 1 
137    ENDDO
138   
139    avpr = avpr_l
140#endif
141
142    avpr = avpr / ( ny + 1 )
143!
144!-- Calculate the disturbances at the recycling plane
145    i = recycling_plane
146
147#if defined( __parallel )
148    IF ( myidx == id_recycling )  THEN
149       DO  l = 1, nbgp
150          DO  j = nysg, nyng
151             DO  k = nzb, nzt + 1
152
153                inflow_dist(k,j,1,l) = u(k,j,i+1) - avpr(k,1,l)
154                inflow_dist(k,j,2,l) = v(k,j,i)   - avpr(k,2,l)
155                inflow_dist(k,j,3,l) = w(k,j,i)   - avpr(k,3,l)
156                inflow_dist(k,j,4,l) = pt(k,j,i)  - avpr(k,4,l)
157                inflow_dist(k,j,5,l) = e(k,j,i)   - avpr(k,5,l)
158             
159            ENDDO
160          ENDDO
161          i = i + 1
162       ENDDO
163
164    ENDIF
165#else
166    DO  l = 1, nbgp
167       DO  j = nysg, nyng
168          DO  k = nzb, nzt+1
169
170             inflow_dist(k,j,1,l) = u(k,j,i+1) - avpr(k,1,l)
171             inflow_dist(k,j,2,l) = v(k,j,i)   - avpr(k,2,l)
172             inflow_dist(k,j,3,l) = w(k,j,i)   - avpr(k,3,l)
173             inflow_dist(k,j,4,l) = pt(k,j,i)  - avpr(k,4,l)
174             inflow_dist(k,j,5,l) = e(k,j,i)   - avpr(k,5,l)
175             
176          ENDDO
177       ENDDO
178       i = i + 1
179    ENDDO
180#endif
181
182!
183!-- For parallel runs, send the disturbances to the respective inflow PE
184#if defined( __parallel )
185    IF ( myidx == id_recycling  .AND.  myidx /= id_inflow )  THEN
186
187       CALL MPI_SEND( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, &
188                      id_inflow, 1, comm1dx, ierr )
189
190    ELSEIF ( myidx /= id_recycling  .AND.  myidx == id_inflow )  THEN
191
192       inflow_dist = 0.0
193       CALL MPI_RECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, &
194                      id_recycling, 1, comm1dx, status, ierr )
195
196    ENDIF
197#endif
198
199!
200!-- Add the disturbance at the inflow
201    IF ( nxl == 0 )  THEN
202
203       DO  j = nysg, nyng
204          DO  k = nzb, nzt + 1
205
206              u(k,j,-nbgp+1:0) = mean_inflow_profiles(k,1) + &
207                           inflow_dist(k,j,1,1:nbgp) * inflow_damping_factor(k)
208              v(k,j,-nbgp:-1)  = mean_inflow_profiles(k,2) + &
209                           inflow_dist(k,j,2,1:nbgp) * inflow_damping_factor(k)
210              w(k,j,-nbgp:-1)  =                             &
211                           inflow_dist(k,j,3,1:nbgp) * inflow_damping_factor(k)
212              pt(k,j,-nbgp:-1) = mean_inflow_profiles(k,4) + &
213                           inflow_dist(k,j,4,1:nbgp) * inflow_damping_factor(k)
214              e(k,j,-nbgp:-1)  = mean_inflow_profiles(k,5) + &
215                           inflow_dist(k,j,5,1:nbgp) * inflow_damping_factor(k)
216              e(k,j,-nbgp:-1)  = MAX( e(k,j,-nbgp:-1), 0.0 )
217
218          ENDDO
219       ENDDO
220
221    ENDIF
222
223    CALL cpu_log( log_point(40), 'inflow_turbulence', 'stop' )
224
225
226 END SUBROUTINE inflow_turbulence
Note: See TracBrowser for help on using the repository browser.