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

Last change on this file since 1319 was 1319, checked in by raasch, 10 years ago

last commit documented

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