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

Last change on this file since 1570 was 1570, checked in by raasch, 9 years ago

last commit documented

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