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

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

Last commit documented.

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