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

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

last commit documented

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