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

Last change on this file since 2 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 6.1 KB
Line 
1 SUBROUTINE exchange_horiz_2d( ar )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: exchange_horiz_2d.f90,v $
11! Revision 1.9  2006/05/12 19:15:52  letzel
12! MPI_REAL replaced by MPI_INTEGER in exchange_horiz_2d_int
13!
14! Revision 1.8  2006/02/23 12:18:32  raasch
15! Additional subroutine exchange_horiz_2d_int for 2D integer arrays,
16! extensions for non-cyclic boundary conditions along x or y for non-parallel
17! case, anz_y renamed ngp_y
18!
19! Revision 1.7  2003/03/16 09:30:43  raasch
20! Two underscores (_) are placed in front of all define-strings
21!
22! Revision 1.6  2002/06/11 12:59:35  raasch
23! Cyclic boundary conditions are used instead of sendrecv in case of
24! pdims(..)=1. Array "feld" is renamed to "ar".
25!
26! Revision 1.5  2001/03/30  07:23:16  07:23:16  raasch (Siegfried Raasch)
27! Translation of remaining German identifiers (variables, subroutines, etc.)
28!
29! Revision 1.4  2001/01/22 06:43:50  raasch
30! Module test_variables removed
31!
32! Revision 1.3  2000/12/20 12:09:27  letzel
33! All comments translated into English.
34!
35! Revision 1.2  1998/07/06 12:13:53  raasch
36! + USE test_variables
37!
38! Revision 1.1  1998/01/23 09:58:21  raasch
39! Initial revision
40!
41!
42! Description:
43! ------------
44! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
45! boundary conditions, respectively, for 2D-arrays.
46!------------------------------------------------------------------------------!
47
48    USE control_parameters
49    USE cpulog
50    USE indices
51    USE interfaces
52    USE pegrid
53
54    IMPLICIT NONE
55
56    REAL ::  ar(nys-1:nyn+1,nxl-1:nxr+1)
57
58
59    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
60
61#if defined( __parallel )
62
63!
64!-- Exchange of lateral boundary values for parallel computers
65    IF ( pdims(1) == 1 )  THEN
66
67!
68!--    One-dimensional decomposition along y, boundary values can be exchanged
69!--    within the PE memory
70       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
71       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
72
73    ELSE
74!
75!--    Send left boundary, receive right one
76       CALL MPI_SENDRECV( ar(nys,nxl),   ngp_y, MPI_REAL, pleft,  0, &
77                          ar(nys,nxr+1), ngp_y, MPI_REAL, pright, 0, &
78                          comm2d, status, ierr )
79!
80!--    Send right boundary, receive left one
81       CALL MPI_SENDRECV( ar(nys,nxr),   ngp_y, MPI_REAL, pright,  1, &
82                          ar(nys,nxl-1), ngp_y, MPI_REAL, pleft,   1, &
83                          comm2d, status, ierr )
84    ENDIF
85
86    IF ( pdims(2) == 1 )  THEN
87!
88!--    One-dimensional decomposition along x, boundary values can be exchanged
89!--    within the PE memory
90       ar(nys-1,:) = ar(nyn,:)
91       ar(nyn+1,:) = ar(nys,:)
92
93    ELSE
94!
95!--    Send front boundary, receive rear one
96       CALL MPI_SENDRECV( ar(nys,nxl-1),   1, type_x, psouth, 0, &
97                          ar(nyn+1,nxl-1), 1, type_x, pnorth, 0, &
98                          comm2d, status, ierr )
99!
100!--    Send rear boundary, receive front one
101       CALL MPI_SENDRECV( ar(nyn,nxl-1),   1, type_x, pnorth, 1, &
102                          ar(nys-1,nxl-1), 1, type_x, psouth, 1, &
103                          comm2d, status, ierr )
104    ENDIF
105
106#else
107
108!
109!-- Lateral boundary conditions in the non-parallel case
110    IF ( bc_lr == 'cyclic' )  THEN
111       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
112       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
113    ENDIF
114
115    IF ( bc_ns == 'cyclic' )  THEN
116       ar(nys-1,:) = ar(nyn,:)
117       ar(nyn+1,:) = ar(nys,:)
118    ENDIF
119
120#endif
121
122    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
123
124 END SUBROUTINE exchange_horiz_2d
125
126
127
128 SUBROUTINE exchange_horiz_2d_int( ar )
129
130!------------------------------------------------------------------------------!
131! Description:
132! ------------
133! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
134! boundary conditions, respectively, for 2D integer arrays.
135!------------------------------------------------------------------------------!
136
137    USE control_parameters
138    USE cpulog
139    USE indices
140    USE interfaces
141    USE pegrid
142
143    IMPLICIT NONE
144
145    INTEGER ::  ar(nys-1:nyn+1,nxl-1:nxr+1)
146
147
148    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
149
150#if defined( __parallel )
151
152!
153!-- Exchange of lateral boundary values for parallel computers
154    IF ( pdims(1) == 1 )  THEN
155
156!
157!--    One-dimensional decomposition along y, boundary values can be exchanged
158!--    within the PE memory
159       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
160       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
161
162    ELSE
163!
164!--    Send left boundary, receive right one
165       CALL MPI_SENDRECV( ar(nys,nxl),   ngp_y, MPI_INTEGER, pleft,  0, &
166                          ar(nys,nxr+1), ngp_y, MPI_INTEGER, pright, 0, &
167                          comm2d, status, ierr )
168!
169!--    Send right boundary, receive left one
170       CALL MPI_SENDRECV( ar(nys,nxr),   ngp_y, MPI_INTEGER, pright,  1, &
171                          ar(nys,nxl-1), ngp_y, MPI_INTEGER, pleft,   1, &
172                          comm2d, status, ierr )
173    ENDIF
174
175    IF ( pdims(2) == 1 )  THEN
176!
177!--    One-dimensional decomposition along x, boundary values can be exchanged
178!--    within the PE memory
179       ar(nys-1,:) = ar(nyn,:)
180       ar(nyn+1,:) = ar(nys,:)
181
182    ELSE
183!
184!--    Send front boundary, receive rear one
185       CALL MPI_SENDRECV( ar(nys,nxl-1),   1, type_x_int, psouth, 0, &
186                          ar(nyn+1,nxl-1), 1, type_x_int, pnorth, 0, &
187                          comm2d, status, ierr )
188!
189!--    Send rear boundary, receive front one
190       CALL MPI_SENDRECV( ar(nyn,nxl-1),   1, type_x_int, pnorth, 1, &
191                          ar(nys-1,nxl-1), 1, type_x_int, psouth, 1, &
192                          comm2d, status, ierr )
193    ENDIF
194
195#else
196
197!
198!-- Lateral boundary conditions in the non-parallel case
199    IF ( bc_lr == 'cyclic' )  THEN
200       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
201       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
202    ENDIF
203
204    IF ( bc_ns == 'cyclic' )  THEN
205       ar(nys-1,:) = ar(nyn,:)
206       ar(nyn+1,:) = ar(nys,:)
207    ENDIF
208
209#endif
210
211    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
212
213 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.