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

Last change on this file since 708 was 708, checked in by raasch, 13 years ago

last commit documented

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