source: palm/trunk/SOURCE/exchange_horiz.f90 @ 1128

Last change on this file since 1128 was 1128, checked in by raasch, 12 years ago

asynchronous transfer of ghost point data for acc-optimized version

  • Property svn:keywords set to Id
File size: 10.1 KB
Line 
1 SUBROUTINE exchange_horiz( ar, nbgp_local)
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! modifications for asynchronous transfer,
23! local variables req, wait_stat are global now, and have been moved to module
24! pegrid
25!
26! Former revisions:
27! -----------------
28! $Id: exchange_horiz.f90 1128 2013-04-12 06:19:32Z raasch $
29!
30! 1113 2013-03-10 02:48:14Z raasch
31! GPU-porting for single-core (1PE) mode
32!
33! 1036 2012-10-22 13:43:42Z raasch
34! code put under GPL (PALM 3.9)
35!
36! 841 2012-02-28 12:29:49Z maronga
37! Excluded routine from compilation of namelist_file_check
38!
39! 709 2011-03-30 09:31:40Z raasch
40! formatting adjustments
41!
42! 707 2011-03-29 11:39:40Z raasch
43! grid_level directly used as index for MPI data type arrays,
44! bc_lr/ns replaced by bc_lr/ns_cyc
45!
46! 689 2011-02-20 19:31:12z gryschka
47! Bugfix for some logical expressions
48! (syntax was not compatible with all compilers)
49!
50! 683 2011-02-09 14:25:15Z raasch
51! optional synchronous exchange (sendrecv) implemented, code partly reformatted
52!
53! 667 2010-12-23 12:06:00Z suehring/gryschka
54! Dynamic exchange of ghost points with nbgp_local to ensure that no useless
55! ghost points exchanged in case of multigrid. type_yz(0) and type_xz(0)
56! used for normal grid, the remaining types used for the several grid levels.
57! Exchange is done via MPI-Vectors with a dynamic value of ghost points which
58! depend on the advection scheme. Exchange of left and right PEs is 10% faster
59! with MPI-Vectors than without.
60!
61! 75 2007-03-22 09:54:05Z raasch
62! Special cases for additional gridpoints along x or y in case of non-cyclic
63! boundary conditions are not regarded any more
64!
65! RCS Log replace by Id keyword, revision history cleaned up
66!
67! Revision 1.16  2006/02/23 12:19:08  raasch
68! anz_yz renamed ngp_yz
69!
70! Revision 1.1  1997/07/24 11:13:29  raasch
71! Initial revision
72!
73!
74! Description:
75! ------------
76! Exchange of lateral boundary values (parallel computers) and cyclic
77! lateral boundary conditions, respectively.
78!------------------------------------------------------------------------------!
79
80    USE control_parameters
81    USE cpulog
82    USE indices
83    USE interfaces
84    USE pegrid
85
86    IMPLICIT NONE
87
88
89    INTEGER ::  i, j, k, nbgp_local
90    REAL, DIMENSION(nzb:nzt+1,nys-nbgp_local:nyn+nbgp_local, &
91                    nxl-nbgp_local:nxr+nbgp_local) ::  ar
92
93#if ! defined( __check )
94
95    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'start' )
96
97#if defined( __parallel )
98
99!
100!-- Exchange in x-direction of lateral boundaries
101    IF ( pdims(1) == 1  .OR.  mg_switch_to_pe0 )  THEN
102!
103!--    One-dimensional decomposition along y, boundary values can be exchanged
104!--    within the PE memory
105       IF ( bc_lr_cyc )  THEN
106          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
107          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
108       ENDIF
109
110    ELSE
111
112       IF ( synchronous_exchange )  THEN
113!
114!--       Send left boundary, receive right one (synchronous)
115          CALL MPI_SENDRECV(                                                   &
116              ar(nzb,nys-nbgp_local,nxl),   1, type_yz(grid_level), pleft,  0, &
117              ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz(grid_level), pright, 0, &
118              comm2d, status, ierr )
119!
120!--       Send right boundary, receive left one (synchronous)
121          CALL MPI_SENDRECV( ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1, &
122                             type_yz(grid_level), pright, 1,             &
123                             ar(nzb,nys-nbgp_local,nxl-nbgp_local), 1,   &
124                             type_yz(grid_level), pleft,  1,             &
125                             comm2d, status, ierr )
126
127       ELSE
128
129!
130!--       In case of background communication switched on, exchange is done
131!--       either along x or along y
132          IF ( send_receive == 'lr'  .OR.  send_receive == 'al' )  THEN
133
134             IF ( .NOT. sendrecv_in_background )  THEN
135                req(1:4)  = 0
136                req_count = 0
137             ENDIF
138!
139!--          Send left boundary, receive right one (asynchronous)
140             CALL MPI_ISEND( ar(nzb,nys-nbgp_local,nxl),   1, type_yz(grid_level), &
141                             pleft, req_count, comm2d, req(req_count+1), ierr )
142             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz(grid_level), &
143                             pright, req_count, comm2d, req(req_count+2), ierr )
144!
145!--          Send right boundary, receive left one (asynchronous)
146             CALL MPI_ISEND( ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1,          &
147                             type_yz(grid_level), pright, req_count+1, comm2d,    &
148                             req(req_count+3), ierr )
149             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,          &
150                             type_yz(grid_level), pleft,  req_count+1, comm2d,    &
151                             req(req_count+4), ierr )
152
153             IF ( .NOT. sendrecv_in_background )  THEN
154                CALL MPI_WAITALL( 4, req, wait_stat, ierr )
155             ELSE
156                req_count = req_count + 4
157             ENDIF
158
159          ENDIF
160
161       ENDIF
162
163    ENDIF
164
165
166    IF ( pdims(2) == 1  .OR.  mg_switch_to_pe0 )  THEN
167!
168!--    One-dimensional decomposition along x, boundary values can be exchanged
169!--    within the PE memory
170       IF ( bc_ns_cyc )  THEN
171          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
172          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
173       ENDIF
174
175    ELSE
176
177       IF ( synchronous_exchange )  THEN
178!
179!--       Send front boundary, receive rear one (synchronous)
180          CALL MPI_SENDRECV(                                                   &
181              ar(nzb,nys,nxl-nbgp_local),   1, type_xz(grid_level), psouth, 0, &
182              ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz(grid_level), pnorth, 0, &
183              comm2d, status, ierr )
184!
185!--       Send rear boundary, receive front one (synchronous)
186          CALL MPI_SENDRECV( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1, &
187                             type_xz(grid_level), pnorth, 1,             &
188                             ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1, &
189                             type_xz(grid_level), psouth, 1,             &
190                             comm2d, status, ierr )
191
192       ELSE
193
194!
195!--       In case of background communication switched on, exchange is done
196!--       either along x or along y
197          IF ( send_receive == 'lr'  .OR.  send_receive == 'al' )  THEN
198
199             IF ( .NOT. sendrecv_in_background )  THEN
200                req(1:4)  = 0
201                req_count = 0
202             ENDIF
203
204!
205!--          Send front boundary, receive rear one (asynchronous)
206             CALL MPI_ISEND( ar(nzb,nys,nxl-nbgp_local),   1, type_xz(grid_level), &
207                             psouth, req_count, comm2d, req(req_count+1), ierr )
208             CALL MPI_IRECV( ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz(grid_level), &
209                             pnorth, req_count, comm2d, req(req_count+2), ierr )
210!
211!--          Send rear boundary, receive front one (asynchronous)
212             CALL MPI_ISEND( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1,          &
213                             type_xz(grid_level), pnorth, req_count+1, comm2d,    &
214                             req(req_count+3), ierr )
215             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,          &
216                             type_xz(grid_level), psouth, req_count+1, comm2d,    &
217                             req(req_count+4), ierr )
218
219             IF ( .NOT. sendrecv_in_background )  THEN
220                CALL MPI_WAITALL( 4, req, wait_stat, ierr )
221             ELSE
222                req_count = req_count + 4
223             ENDIF
224
225          ENDIF
226
227       ENDIF
228
229    ENDIF
230
231#else
232
233!
234!-- Lateral boundary conditions in the non-parallel case.
235!-- Case dependent, because in GPU mode still not all arrays are on device. This
236!-- workaround has to be removed later. Also, since PGI compiler 12.5 has problems
237!-- with array syntax, explicit loops are used.
238    IF ( bc_lr == 'cyclic' )  THEN
239       IF ( on_device )  THEN
240          !$acc kernels present( ar )
241          !$acc loop independent
242          DO  i = 0, nbgp_local-1
243             DO  j = nys-nbgp_local, nyn+nbgp_local
244                !$acc loop vector( 32 )
245                DO  k = nzb, nzt+1
246                   ar(k,j,nxl-nbgp_local+i) = ar(k,j,nxr-nbgp_local+1+i)
247                   ar(k,j,nxr+1+i)          = ar(k,j,nxl+i)
248                ENDDO
249             ENDDO
250          ENDDO
251          !$acc end kernels
252       ELSE
253          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
254          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
255       ENDIF
256    ENDIF
257
258    IF ( bc_ns == 'cyclic' )  THEN
259       IF ( on_device )  THEN
260          !$acc kernels present( ar )
261          !$acc loop
262          DO  i = nxl-nbgp_local, nxr+nbgp_local
263             !$acc loop independent
264             DO  j = 0, nbgp_local-1
265                !$acc loop vector( 32 )
266                DO  k = nzb, nzt+1
267                   ar(k,nys-nbgp_local+j,i) = ar(k,nyn-nbgp_local+1+j,i)
268                     ar(k,nyn+1+j,i)          = ar(k,nys+j,i)
269                ENDDO
270             ENDDO
271          ENDDO
272          !$acc end kernels
273       ELSE
274          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
275          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
276       ENDIF
277    ENDIF
278
279#endif
280    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'stop' )
281
282#endif
283 END SUBROUTINE exchange_horiz
Note: See TracBrowser for help on using the repository browser.