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

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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