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

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