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

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

preliminary changes for radiation conditions

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