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

Last change on this file since 931 was 842, checked in by maronga, 12 years ago

last commit documented

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