source: palm/trunk/SOURCE/exchange_horiz_2d.f90 @ 702

Last change on this file since 702 was 702, checked in by suehring, 13 years ago

Removed bugfix in exchange_horiz_2d_int().

  • Property svn:keywords set to Id
File size: 6.6 KB
Line 
1 SUBROUTINE exchange_horiz_2d( ar )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7! Bugfix in declaration of ar in exchange_horiz_2d_int and number of MPI-blocks
8! in MPI_SENDRECV().
9!
10! Former revisions:
11! -----------------
12! $Id: exchange_horiz_2d.f90 702 2011-03-24 19:33:15Z suehring $
13!
14! 667 2010-12-23 12:06:00Z suehring/gryschka
15! Dynamic exchange of ghost points with nbgp, which depends on the advection
16! scheme. Exchange between left and right PEs is now done with MPI-vectors.
17!
18! 73 2007-03-20 08:33:14Z raasch
19! Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary
20! conditions
21!
22! RCS Log replace by Id keyword, revision history cleaned up
23!
24! Revision 1.9  2006/05/12 19:15:52  letzel
25! MPI_REAL replaced by MPI_INTEGER in exchange_horiz_2d_int
26!
27! Revision 1.1  1998/01/23 09:58:21  raasch
28! Initial revision
29!
30!
31! Description:
32! ------------
33! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
34! boundary conditions, respectively, for 2D-arrays.
35!------------------------------------------------------------------------------!
36
37    USE control_parameters
38    USE cpulog
39    USE indices
40    USE interfaces
41    USE pegrid
42
43    IMPLICIT NONE
44
45    REAL ::  ar(nysg:nyng,nxlg:nxrg)
46    INTEGER :: i
47
48
49    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
50
51#if defined( __parallel )
52
53!
54!-- Exchange of lateral boundary values for parallel computers
55    IF ( pdims(1) == 1 )  THEN
56
57!
58!--    One-dimensional decomposition along y, boundary values can be exchanged
59!--    within the PE memory
60       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
61       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
62
63    ELSE
64!
65!--    Send left boundary, receive right one
66
67       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y, pleft,  0,                 &
68                          ar(nysg,nxr+1), 1, type_y, pright, 0,               &
69                          comm2d, status, ierr )
70!
71!--    Send right boundary, receive left one
72       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y, pright,  1,         &
73                          ar(nysg,nxlg), 1, type_y, pleft,   1,               &
74                          comm2d, status, ierr )
75                         
76     
77    ENDIF
78
79    IF ( pdims(2) == 1 )  THEN
80!
81!--    One-dimensional decomposition along x, boundary values can be exchanged
82!--    within the PE memory
83       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
84       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
85
86    ELSE
87!
88!--    Send front boundary, receive rear one
89
90       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x, psouth, 0,                 &         
91                          ar(nyn+1,nxlg), 1, type_x, pnorth, 0,               &
92                          comm2d, status, ierr )
93!
94!--    Send rear boundary, receive front one
95       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x, pnorth, 1,          &
96                          ar(nysg,nxlg), 1, type_x, psouth, 1,                &
97                          comm2d, status, ierr )
98
99    ENDIF
100
101#else
102
103!
104!-- Lateral boundary conditions in the non-parallel case
105    IF ( bc_lr == 'cyclic' )  THEN
106       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
107       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
108    ENDIF
109
110    IF ( bc_ns == 'cyclic' )  THEN
111       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
112       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
113    ENDIF
114
115
116#endif
117
118!
119!-- Neumann-conditions at inflow/outflow in case of non-cyclic boundary
120!-- conditions
121    IF ( inflow_l .OR. outflow_l )  THEN
122       DO i=nbgp, 1, -1
123         ar(:,nxl-i) = ar(:,nxl)
124       END DO
125    END IF
126    IF ( inflow_r .OR. outflow_r )  THEN
127       DO i=1, nbgp
128          ar(:,nxr+i) = ar(:,nxr)
129       END DO
130    END IF
131    IF ( inflow_s .OR. outflow_s )  THEN
132       DO i=nbgp, 1, -1
133         ar(nys-i,:) = ar(nys,:)
134       END DO
135    END IF
136    IF ( inflow_n .OR. outflow_n )  THEN
137       DO i=1, nbgp
138         ar(nyn+i,:) = ar(nyn,:)
139       END DO
140    END IF
141    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
142
143 END SUBROUTINE exchange_horiz_2d
144
145
146
147 SUBROUTINE exchange_horiz_2d_int( ar )
148
149!------------------------------------------------------------------------------!
150! Description:
151! ------------
152! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
153! boundary conditions, respectively, for 2D integer arrays.
154!------------------------------------------------------------------------------!
155
156    USE control_parameters
157    USE cpulog
158    USE indices
159    USE interfaces
160    USE pegrid
161
162    IMPLICIT NONE
163
164    INTEGER ::  ar(nysg:nyng,nxlg:nxrg)
165    INTEGER :: i
166
167    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
168
169#if defined( __parallel )
170
171!
172!-- Exchange of lateral boundary values for parallel computers
173    IF ( pdims(1) == 1 )  THEN
174
175!
176!--    One-dimensional decomposition along y, boundary values can be exchanged
177!--    within the PE memory
178       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
179       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
180
181
182    ELSE
183!
184!--    Send left boundary, receive right one
185       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y_int, pleft,  0,             &
186                          ar(nysg,nxr+1), 1, type_y_int, pright, 0,           &
187                          comm2d, status, ierr )
188!
189!--    Send right boundary, receive left one
190       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y_int, pright,  1,     &
191                          ar(nysg,nxlg), 1, type_y_int, pleft,   1,           &
192                          comm2d, status, ierr )
193
194    ENDIF
195
196    IF ( pdims(2) == 1 )  THEN
197!
198!--    One-dimensional decomposition along x, boundary values can be exchanged
199!--    within the PE memory
200       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
201       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
202
203
204    ELSE
205!
206!--    Send front boundary, receive rear one
207       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x_int, psouth, 0,             &
208                          ar(nyn+1,nxlg), 1, type_x_int, pnorth, 0,           &
209                          comm2d, status, ierr )                         
210
211!
212!--    Send rear boundary, receive front one
213       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x_int, pnorth, 1,      &
214                          ar(nysg,nxlg), 1, type_x_int, psouth, 1,            &
215                          comm2d, status, ierr )
216
217    ENDIF
218
219#else
220
221!
222!-- Lateral boundary conditions in the non-parallel case
223    IF ( bc_lr == 'cyclic' )  THEN
224       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
225       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
226    ENDIF
227
228    IF ( bc_ns == 'cyclic' )  THEN
229       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
230       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
231    ENDIF
232
233#endif
234    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
235
236 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.