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

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

bugfix: missed variables added to ONLY-list

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