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

Last change on this file since 841 was 841, checked in by maronga, 13 years ago

further adjustments and bugfixes for the namelist file check

  • 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! -----------------
[841]6! Excluded routine from compilation of namelist_file_check
[1]7!
8! Former revisions:
9! -----------------
[3]10! $Id: exchange_horiz_2d.f90 841 2012-02-28 12:29:49Z maronga $
[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
[841]50
[667]51    REAL ::  ar(nysg:nyng,nxlg:nxrg)
52    INTEGER :: i
[1]53
[841]54#if ! defined( __check )
[1]55    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
56
57#if defined( __parallel )
58
59!
60!-- Exchange of lateral boundary values for parallel computers
61    IF ( pdims(1) == 1 )  THEN
62
63!
64!--    One-dimensional decomposition along y, boundary values can be exchanged
65!--    within the PE memory
[702]66       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
67       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]68
69    ELSE
70!
71!--    Send left boundary, receive right one
[667]72
[702]73       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y, pleft,  0,                 &
74                          ar(nysg,nxr+1), 1, type_y, pright, 0,               &
[1]75                          comm2d, status, ierr )
76!
77!--    Send right boundary, receive left one
[702]78       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y, pright,  1,         &
79                          ar(nysg,nxlg), 1, type_y, pleft,   1,               &
[1]80                          comm2d, status, ierr )
[702]81                         
82     
[1]83    ENDIF
84
85    IF ( pdims(2) == 1 )  THEN
86!
87!--    One-dimensional decomposition along x, boundary values can be exchanged
88!--    within the PE memory
[702]89       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
90       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
[1]91
92    ELSE
93!
94!--    Send front boundary, receive rear one
[667]95
[702]96       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x, psouth, 0,                 &         
97                          ar(nyn+1,nxlg), 1, type_x, pnorth, 0,               &
[1]98                          comm2d, status, ierr )
99!
100!--    Send rear boundary, receive front one
[702]101       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x, pnorth, 1,          &
102                          ar(nysg,nxlg), 1, type_x, psouth, 1,                &
[1]103                          comm2d, status, ierr )
[667]104
[1]105    ENDIF
106
107#else
108
109!
110!-- Lateral boundary conditions in the non-parallel case
[707]111    IF ( bc_lr_cyc )  THEN
[702]112       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
113       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]114    ENDIF
115
[707]116    IF ( bc_ns_cyc )  THEN
[702]117       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
118       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
[1]119    ENDIF
120
[667]121
[1]122#endif
123
[73]124!
125!-- Neumann-conditions at inflow/outflow in case of non-cyclic boundary
126!-- conditions
[667]127    IF ( inflow_l .OR. outflow_l )  THEN
128       DO i=nbgp, 1, -1
129         ar(:,nxl-i) = ar(:,nxl)
130       END DO
131    END IF
132    IF ( inflow_r .OR. outflow_r )  THEN
133       DO i=1, nbgp
134          ar(:,nxr+i) = ar(:,nxr)
135       END DO
136    END IF
137    IF ( inflow_s .OR. outflow_s )  THEN
138       DO i=nbgp, 1, -1
139         ar(nys-i,:) = ar(nys,:)
140       END DO
141    END IF
142    IF ( inflow_n .OR. outflow_n )  THEN
143       DO i=1, nbgp
144         ar(nyn+i,:) = ar(nyn,:)
145       END DO
146    END IF
[1]147    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
148
[841]149#endif
[1]150 END SUBROUTINE exchange_horiz_2d
151
152
153
154 SUBROUTINE exchange_horiz_2d_int( ar )
155
156!------------------------------------------------------------------------------!
157! Description:
158! ------------
159! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
160! boundary conditions, respectively, for 2D integer arrays.
161!------------------------------------------------------------------------------!
162
163    USE control_parameters
164    USE cpulog
165    USE indices
166    USE interfaces
167    USE pegrid
168
169    IMPLICIT NONE
170
[702]171    INTEGER ::  ar(nysg:nyng,nxlg:nxrg)
[667]172    INTEGER :: i
[1]173
[841]174#if ! defined( __check )
[1]175    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
176
177#if defined( __parallel )
178
179!
180!-- Exchange of lateral boundary values for parallel computers
181    IF ( pdims(1) == 1 )  THEN
182
183!
184!--    One-dimensional decomposition along y, boundary values can be exchanged
185!--    within the PE memory
[702]186       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
187       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]188
[702]189
[1]190    ELSE
191!
192!--    Send left boundary, receive right one
[702]193       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y_int, pleft,  0,             &
194                          ar(nysg,nxr+1), 1, type_y_int, pright, 0,           &
[1]195                          comm2d, status, ierr )
196!
197!--    Send right boundary, receive left one
[702]198       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y_int, pright,  1,     &
199                          ar(nysg,nxlg), 1, type_y_int, pleft,   1,           &
[1]200                          comm2d, status, ierr )
[667]201
[1]202    ENDIF
203
204    IF ( pdims(2) == 1 )  THEN
205!
206!--    One-dimensional decomposition along x, boundary values can be exchanged
207!--    within the PE memory
[667]208       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
209       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
[1]210
[667]211
[1]212    ELSE
213!
214!--    Send front boundary, receive rear one
[702]215       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x_int, psouth, 0,             &
216                          ar(nyn+1,nxlg), 1, type_x_int, pnorth, 0,           &
217                          comm2d, status, ierr )                         
[667]218
[1]219!
220!--    Send rear boundary, receive front one
[702]221       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x_int, pnorth, 1,      &
222                          ar(nysg,nxlg), 1, type_x_int, psouth, 1,            &
[1]223                          comm2d, status, ierr )
[667]224
[1]225    ENDIF
226
227#else
228
229!
230!-- Lateral boundary conditions in the non-parallel case
[707]231    IF ( bc_lr_cyc )  THEN
[702]232       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
233       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]234    ENDIF
235
[707]236    IF ( bc_ns_cyc )  THEN
[667]237       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
238       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
[1]239    ENDIF
240
241#endif
242    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
243
[841]244#endif
[1]245 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.