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

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

last commit documented

  • Property svn:keywords set to Id
File size: 10.0 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 1321 2014-03-20 09:40:40Z raasch $
27!
28! 1320 2014-03-20 08:40:49Z raasch
29! ONLY-attribute added to USE-statements,
30! kind-parameters added to all INTEGER and REAL declaration statements,
31! kinds are defined in new module kinds,
32! revision history before 2012 removed,
33! comment fields (!:) to be used for variable explanations added to
34! all variable declaration statements
35!
36! 1257 2013-11-08 15:18:40Z raasch
37! openacc loop and loop vector clauses removed
38!
39! 1128 2013-04-12 06:19:32Z raasch
40! modifications for asynchronous transfer,
41! local variables req, wait_stat are global now, and have been moved to module
42! pegrid
43!
44! 1113 2013-03-10 02:48:14Z raasch
45! GPU-porting for single-core (1PE) mode
46!
47! 1036 2012-10-22 13:43:42Z raasch
48! code put under GPL (PALM 3.9)
49!
50! 841 2012-02-28 12:29:49Z maronga
51! Excluded routine from compilation of namelist_file_check
52!
53! Revision 1.1  1997/07/24 11:13:29  raasch
54! Initial revision
55!
56!
57! Description:
58! ------------
59! Exchange of lateral boundary values (parallel computers) and cyclic
60! lateral boundary conditions, respectively.
61!------------------------------------------------------------------------------!
62
63    USE control_parameters,                                                    &
64        ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, mg_switch_to_pe0,             &
65               synchronous_exchange
66               
67    USE cpulog,                                                                &
68        ONLY:  cpu_log, log_point_s
69       
70    USE indices,                                                               &
71        ONLY:  nxl, nxr, nyn, nys, nzb, nzt
72       
73    USE kinds
74   
75    USE pegrid
76
77    IMPLICIT NONE
78
79
80    INTEGER(iwp) ::  i           !:
81    INTEGER(iwp) ::  j           !:
82    INTEGER(iwp) ::  k           !:
83    INTEGER(iwp) ::  nbgp_local  !:
84   
85    REAL(wp), DIMENSION(nzb:nzt+1,nys-nbgp_local:nyn+nbgp_local,               &
86                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !:
87                       
88
89#if ! defined( __check )
90
91    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'start' )
92
93#if defined( __parallel )
94
95!
96!-- Exchange in x-direction of lateral boundaries
97    IF ( pdims(1) == 1  .OR.  mg_switch_to_pe0 )  THEN
98!
99!--    One-dimensional decomposition along y, boundary values can be exchanged
100!--    within the PE memory
101       IF ( bc_lr_cyc )  THEN
102          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
103          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
104       ENDIF
105
106    ELSE
107
108       IF ( synchronous_exchange )  THEN
109!
110!--       Send left boundary, receive right one (synchronous)
111          CALL MPI_SENDRECV(                                                   &
112              ar(nzb,nys-nbgp_local,nxl),   1, type_yz(grid_level), pleft,  0, &
113              ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz(grid_level), pright, 0, &
114              comm2d, status, ierr )
115!
116!--       Send right boundary, receive left one (synchronous)
117          CALL MPI_SENDRECV( ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1,       &
118                             type_yz(grid_level), pright, 1,                   &
119                             ar(nzb,nys-nbgp_local,nxl-nbgp_local), 1,         &
120                             type_yz(grid_level), pleft,  1,                   &
121                             comm2d, status, ierr )
122
123       ELSE
124
125!
126!--       In case of background communication switched on, exchange is done
127!--       either along x or along y
128          IF ( send_receive == 'lr'  .OR.  send_receive == 'al' )  THEN
129
130             IF ( .NOT. sendrecv_in_background )  THEN
131                req(1:4)  = 0
132                req_count = 0
133             ENDIF
134!
135!--          Send left boundary, receive right one (asynchronous)
136             CALL MPI_ISEND( ar(nzb,nys-nbgp_local,nxl),   1, type_yz(grid_level), &
137                             pleft, req_count, comm2d, req(req_count+1), ierr )
138             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz(grid_level), &
139                             pright, req_count, comm2d, req(req_count+2), ierr )
140!
141!--          Send right boundary, receive left one (asynchronous)
142             CALL MPI_ISEND( ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1,       &
143                             type_yz(grid_level), pright, req_count+1, comm2d, &
144                             req(req_count+3), ierr )
145             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,       &
146                             type_yz(grid_level), pleft,  req_count+1, comm2d, &
147                             req(req_count+4), ierr )
148
149             IF ( .NOT. sendrecv_in_background )  THEN
150                CALL MPI_WAITALL( 4, req, wait_stat, ierr )
151             ELSE
152                req_count = req_count + 4
153             ENDIF
154
155          ENDIF
156
157       ENDIF
158
159    ENDIF
160
161
162    IF ( pdims(2) == 1  .OR.  mg_switch_to_pe0 )  THEN
163!
164!--    One-dimensional decomposition along x, boundary values can be exchanged
165!--    within the PE memory
166       IF ( bc_ns_cyc )  THEN
167          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
168          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
169       ENDIF
170
171    ELSE
172
173       IF ( synchronous_exchange )  THEN
174!
175!--       Send front boundary, receive rear one (synchronous)
176          CALL MPI_SENDRECV(                                                   &
177              ar(nzb,nys,nxl-nbgp_local),   1, type_xz(grid_level), psouth, 0, &
178              ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz(grid_level), pnorth, 0, &
179              comm2d, status, ierr )
180!
181!--       Send rear boundary, receive front one (synchronous)
182          CALL MPI_SENDRECV( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1,       &
183                             type_xz(grid_level), pnorth, 1,                   &
184                             ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,       &
185                             type_xz(grid_level), psouth, 1,                   &
186                             comm2d, status, ierr )
187
188       ELSE
189
190!
191!--       In case of background communication switched on, exchange is done
192!--       either along x or along y
193          IF ( send_receive == 'lr'  .OR.  send_receive == 'al' )  THEN
194
195             IF ( .NOT. sendrecv_in_background )  THEN
196                req(1:4)  = 0
197                req_count = 0
198             ENDIF
199
200!
201!--          Send front boundary, receive rear one (asynchronous)
202             CALL MPI_ISEND( ar(nzb,nys,nxl-nbgp_local),   1, type_xz(grid_level), &
203                             psouth, req_count, comm2d, req(req_count+1), ierr )
204             CALL MPI_IRECV( ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz(grid_level), &
205                             pnorth, req_count, comm2d, req(req_count+2), ierr )
206!
207!--          Send rear boundary, receive front one (asynchronous)
208             CALL MPI_ISEND( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1,       &
209                             type_xz(grid_level), pnorth, req_count+1, comm2d, &
210                             req(req_count+3), ierr )
211             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,       &
212                             type_xz(grid_level), psouth, req_count+1, comm2d, &
213                             req(req_count+4), ierr )
214
215             IF ( .NOT. sendrecv_in_background )  THEN
216                CALL MPI_WAITALL( 4, req, wait_stat, ierr )
217             ELSE
218                req_count = req_count + 4
219             ENDIF
220
221          ENDIF
222
223       ENDIF
224
225    ENDIF
226
227#else
228
229!
230!-- Lateral boundary conditions in the non-parallel case.
231!-- Case dependent, because in GPU mode still not all arrays are on device. This
232!-- workaround has to be removed later. Also, since PGI compiler 12.5 has problems
233!-- with array syntax, explicit loops are used.
234    IF ( bc_lr == 'cyclic' )  THEN
235       IF ( on_device )  THEN
236          !$acc kernels present( ar )
237          !$acc loop independent
238          DO  i = 0, nbgp_local-1
239             DO  j = nys-nbgp_local, nyn+nbgp_local
240                DO  k = nzb, nzt+1
241                   ar(k,j,nxl-nbgp_local+i) = ar(k,j,nxr-nbgp_local+1+i)
242                   ar(k,j,nxr+1+i)          = ar(k,j,nxl+i)
243                ENDDO
244             ENDDO
245          ENDDO
246          !$acc end kernels
247       ELSE
248          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
249          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
250       ENDIF
251    ENDIF
252
253    IF ( bc_ns == 'cyclic' )  THEN
254       IF ( on_device )  THEN
255          !$acc kernels present( ar )
256          DO  i = nxl-nbgp_local, nxr+nbgp_local
257             !$acc loop independent
258             DO  j = 0, nbgp_local-1
259                !$acc loop independent
260                DO  k = nzb, nzt+1
261                   ar(k,nys-nbgp_local+j,i) = ar(k,nyn-nbgp_local+1+j,i)
262                     ar(k,nyn+1+j,i)          = ar(k,nys+j,i)
263                ENDDO
264             ENDDO
265          ENDDO
266          !$acc end kernels
267       ELSE
268          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
269          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
270       ENDIF
271    ENDIF
272
273#endif
274    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'stop' )
275
276#endif
277 END SUBROUTINE exchange_horiz
Note: See TracBrowser for help on using the repository browser.