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

Last change on this file since 647 was 623, checked in by raasch, 13 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 6.5 KB
Line 
1 SUBROUTINE inflow_turbulence
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: inflow_turbulence.f90 623 2010-12-10 08:52:17Z raasch $
11!
12! 622 2010-12-10 08:08:13Z raasch
13! optional barriers included in order to speed up collective operations
14!
15! 222 2009-01-12 16:04:16Z letzel
16! Bugfix for nonparallel execution
17!
18! Initial version (2008/03/07)
19!
20! Description:
21! ------------
22! Imposing turbulence at the respective inflow using the turbulence
23! recycling method of Kataoka and Mizuno (2002).
24!------------------------------------------------------------------------------!
25
26    USE arrays_3d
27    USE control_parameters
28    USE cpulog
29    USE grid_variables
30    USE indices
31    USE interfaces
32    USE pegrid
33
34
35    IMPLICIT NONE
36
37    INTEGER ::  i, imax, j, k, ngp_ifd, ngp_pr
38
39    REAL, DIMENSION(1:2) ::  volume_flow_l, volume_flow_offset
40    REAL, DIMENSION(nzb:nzt+1,5) ::  avpr, avpr_l
41    REAL, DIMENSION(nzb:nzt+1,nys-1:nyn+1,5) ::  inflow_dist
42
43    CALL cpu_log( log_point(40), 'inflow_turbulence', 'start' )
44
45!
46!-- Carry out horizontal averaging in the recycling plane
47    avpr_l = 0.0
48    ngp_pr = ( nzt - nzb + 2 ) * 5
49    ngp_ifd = ngp_pr * ( nyn - nys + 3 )
50
51!
52!-- First, local averaging within the recycling domain
53    IF ( recycling_plane >= nxl )  THEN
54
55       imax = MIN( nxr, recycling_plane )
56
57       DO  i = nxl, imax
58          DO  j = nys, nyn
59             DO  k = nzb, nzt+1
60
61                avpr_l(k,1) = avpr_l(k,1) + u(k,j,i)
62                avpr_l(k,2) = avpr_l(k,2) + v(k,j,i)
63                avpr_l(k,3) = avpr_l(k,3) + w(k,j,i)
64                avpr_l(k,4) = avpr_l(k,4) + pt(k,j,i)
65                avpr_l(k,5) = avpr_l(k,5) + e(k,j,i)
66
67             ENDDO
68          ENDDO
69       ENDDO
70
71    ENDIF
72
73!    WRITE (9,*) '*** averaged profiles avpr_l'
74!    DO  k = nzb, nzt+1
75!       WRITE (9,'(F5.1,1X,F5.1,1X,F5.1,1X,F6.1,1X,F7.2)') avpr_l(k,1),avpr_l(k,2),avpr_l(k,3),avpr_l(k,4),avpr_l(k,5)
76!    ENDDO
77!    WRITE (9,*) ' '
78
79#if defined( __parallel )
80!
81!-- Now, averaging over all PEs
82    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
83    CALL MPI_ALLREDUCE( avpr_l(nzb,1), avpr(nzb,1), ngp_pr, MPI_REAL, MPI_SUM, &
84                        comm2d, ierr )
85#else
86    avpr = avpr_l
87#endif
88
89    avpr = avpr / ( ( ny + 1 ) * ( recycling_plane + 1 ) )
90
91!    WRITE (9,*) '*** averaged profiles'
92!    DO  k = nzb, nzt+1
93!       WRITE (9,'(F5.1,1X,F5.1,1X,F5.1,1X,F6.1,1X,F7.2)') avpr(k,1),avpr(k,2),avpr(k,3),avpr(k,4),avpr(k,5)
94!    ENDDO
95!    WRITE (9,*) ' '
96
97!
98!-- Calculate the disturbances at the recycling plane
99    i = recycling_plane
100
101#if defined( __parallel )
102    IF ( myidx == id_recycling )  THEN
103
104       DO  j = nys-1, nyn+1
105          DO  k = nzb, nzt+1
106
107              inflow_dist(k,j,1) = u(k,j,i+1) - avpr(k,1)
108              inflow_dist(k,j,2) = v(k,j,i)   - avpr(k,2)
109              inflow_dist(k,j,3) = w(k,j,i)   - avpr(k,3)
110              inflow_dist(k,j,4) = pt(k,j,i)  - avpr(k,4)
111              inflow_dist(k,j,5) = e(k,j,i)   - avpr(k,5)
112
113          ENDDO
114       ENDDO
115
116    ENDIF
117#else
118    DO  j = nys-1, nyn+1
119       DO  k = nzb, nzt+1
120
121          inflow_dist(k,j,1) = u(k,j,i+1) - avpr(k,1)
122          inflow_dist(k,j,2) = v(k,j,i)   - avpr(k,2)
123          inflow_dist(k,j,3) = w(k,j,i)   - avpr(k,3)
124          inflow_dist(k,j,4) = pt(k,j,i)  - avpr(k,4)
125          inflow_dist(k,j,5) = e(k,j,i)   - avpr(k,5)
126
127       ENDDO
128    ENDDO
129#endif
130
131!
132!-- For parallel runs, send the disturbances to the respective inflow PE
133#if defined( __parallel )
134    IF ( myidx == id_recycling  .AND.  myidx /= id_inflow )  THEN
135
136       CALL MPI_SEND( inflow_dist(nzb,nys-1,1), ngp_ifd, MPI_REAL, &
137                      id_inflow, 1, comm1dx, ierr )
138
139    ELSEIF ( myidx /= id_recycling  .AND.  myidx == id_inflow )  THEN
140
141       inflow_dist = 0.0
142       CALL MPI_RECV( inflow_dist(nzb,nys-1,1), ngp_ifd, MPI_REAL, &
143                      id_recycling, 1, comm1dx, status, ierr )
144
145    ENDIF
146#endif
147
148!
149!-- Add the disturbance at the inflow
150    IF ( nxl == 0 )  THEN
151
152       DO  j = nys-1, nyn+1
153          DO  k = nzb, nzt+1
154
155!              WRITE (9,*) 'j=',j,' k=',k
156!              WRITE (9,*) 'mean_u = ', mean_inflow_profiles(k,1), ' dist_u = ',&
157!                          inflow_dist(k,j,1)
158!              WRITE (9,*) 'mean_v = ', mean_inflow_profiles(k,2), ' dist_v = ',&
159!                          inflow_dist(k,j,2)
160!              WRITE (9,*) 'mean_w = 0.0', ' dist_w = ',&
161!                          inflow_dist(k,j,3)
162!              WRITE (9,*) 'mean_pt = ', mean_inflow_profiles(k,4), ' dist_pt = ',&
163!                          inflow_dist(k,j,4)
164!              WRITE (9,*) 'mean_e = ', mean_inflow_profiles(k,5), ' dist_e = ',&
165!                          inflow_dist(k,j,5)
166              u(k,j,0)   = mean_inflow_profiles(k,1) + &
167                           inflow_dist(k,j,1) * inflow_damping_factor(k)
168              v(k,j,-1)  = mean_inflow_profiles(k,2) + &
169                           inflow_dist(k,j,2) * inflow_damping_factor(k)
170              w(k,j,-1)  = inflow_dist(k,j,3) * inflow_damping_factor(k)
171              pt(k,j,-1) = mean_inflow_profiles(k,4) + &
172                           inflow_dist(k,j,4) * inflow_damping_factor(k)
173              e(k,j,-1)  = mean_inflow_profiles(k,5) + &
174                           inflow_dist(k,j,5) * inflow_damping_factor(k)
175              e(k,j,-1)  = MAX( e(k,j,-1), 0.0 )
176
177          ENDDO
178       ENDDO
179
180    ENDIF
181
182!
183!-- Conserve the volume flow at the inflow in order to avoid generation of
184!-- waves in the stable layer
185!    IF ( conserve_volume_flow  .AND.  inflow_l )  THEN
186
187!       volume_flow(1)   = 0.0
188!       volume_flow_l(1) = 0.0
189
190!       i = 0
191
192!       DO  j = nys, nyn
193!
194!--       Sum up the volume flow through the south/north boundary
195!          DO  k = nzb_2d(j,i) + 1, nzt
196!             volume_flow_l(1) = volume_flow_l(1) + u(k,j,i) * dzu(k)
197!          ENDDO
198!       ENDDO
199
200#if defined( __parallel )   
201!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
202!       CALL MPI_ALLREDUCE( volume_flow_l(1), volume_flow(1), 1, MPI_REAL, &
203!                           MPI_SUM, comm1dy, ierr )   
204#else
205!       volume_flow = volume_flow_l 
206#endif
207!       volume_flow_offset(1) = ( volume_flow_initial(1) - volume_flow(1) )    &
208!                               / volume_flow_area(1)
209
210!       DO  j = nys-1, nyn+1
211!          DO  k = nzb_v_inner(j,i) + 1, nzt
212!             u(k,j,i) = u(k,j,i) + volume_flow_offset(1)
213!          ENDDO
214!       ENDDO
215
216!    ENDIF
217
218    CALL cpu_log( log_point(40), 'inflow_turbulence', 'stop' )
219
220
221 END SUBROUTINE inflow_turbulence
Note: See TracBrowser for help on using the repository browser.