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

Last change on this file since 550 was 484, checked in by raasch, 14 years ago

typo in file headers removed

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