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

Last change on this file since 1746 was 1683, checked in by knoop, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 13.8 KB
Line 
1!> @file exchange_horiz.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014 Leibniz Universitaet Hannover
17!------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: exchange_horiz.f90 1683 2015-10-07 23:57:51Z gronemeier $
26!
27! 1682 2015-10-07 23:56:08Z knoop
28! Code annotations made doxygen readable
29!
30! 1677 2015-10-02 13:25:23Z boeske
31! Added new routine for exchange of three-dimensional integer arrays
32!
33! 1569 2015-03-12 07:54:38Z raasch
34! bugfix in background communication part
35!
36! 1348 2014-03-27 18:01:03Z raasch
37! bugfix: on_device added to ONLY-list
38!
39! 1344 2014-03-26 17:33:09Z kanani
40! Added missing parameters to ONLY-attribute
41!
42! 1320 2014-03-20 08:40:49Z raasch
43! ONLY-attribute added to USE-statements,
44! kind-parameters added to all INTEGER and REAL declaration statements,
45! kinds are defined in new module kinds,
46! revision history before 2012 removed,
47! comment fields (!:) to be used for variable explanations added to
48! all variable declaration statements
49!
50! 1257 2013-11-08 15:18:40Z raasch
51! openacc loop and loop vector clauses removed
52!
53! 1128 2013-04-12 06:19:32Z raasch
54! modifications for asynchronous transfer,
55! local variables req, wait_stat are global now, and have been moved to module
56! pegrid
57!
58! 1113 2013-03-10 02:48:14Z raasch
59! GPU-porting for single-core (1PE) mode
60!
61! 1036 2012-10-22 13:43:42Z raasch
62! code put under GPL (PALM 3.9)
63!
64! 841 2012-02-28 12:29:49Z maronga
65! Excluded routine from compilation of namelist_file_check
66!
67! Revision 1.1  1997/07/24 11:13:29  raasch
68! Initial revision
69!
70!
71! Description:
72! ------------
73!> Exchange of lateral boundary values (parallel computers) and cyclic
74!> lateral boundary conditions, respectively.
75!------------------------------------------------------------------------------!
76 SUBROUTINE exchange_horiz( ar, nbgp_local)
77 
78
79    USE control_parameters,                                                    &
80        ONLY:  bc_lr, bc_lr_cyc, bc_ns, bc_ns_cyc, grid_level,                 &
81               mg_switch_to_pe0, on_device, synchronous_exchange
82               
83    USE cpulog,                                                                &
84        ONLY:  cpu_log, log_point_s
85       
86    USE indices,                                                               &
87        ONLY:  nxl, nxr, nyn, nys, nzb, nzt
88       
89    USE kinds
90   
91    USE pegrid
92
93    IMPLICIT NONE
94
95
96    INTEGER(iwp) ::  i           !<
97    INTEGER(iwp) ::  j           !<
98    INTEGER(iwp) ::  k           !<
99    INTEGER(iwp) ::  nbgp_local  !<
100   
101    REAL(wp), DIMENSION(nzb:nzt+1,nys-nbgp_local:nyn+nbgp_local,               &
102                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !<
103                       
104
105#if ! defined( __check )
106
107    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'start' )
108
109#if defined( __parallel )
110
111!
112!-- Exchange in x-direction of lateral boundaries
113    IF ( pdims(1) == 1  .OR.  mg_switch_to_pe0 )  THEN
114!
115!--    One-dimensional decomposition along y, boundary values can be exchanged
116!--    within the PE memory
117       IF ( bc_lr_cyc )  THEN
118          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
119          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
120       ENDIF
121
122    ELSE
123
124       IF ( synchronous_exchange )  THEN
125!
126!--       Send left boundary, receive right one (synchronous)
127          CALL MPI_SENDRECV(                                                   &
128              ar(nzb,nys-nbgp_local,nxl),   1, type_yz(grid_level), pleft,  0, &
129              ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz(grid_level), pright, 0, &
130              comm2d, status, ierr )
131!
132!--       Send right boundary, receive left one (synchronous)
133          CALL MPI_SENDRECV( ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1,       &
134                             type_yz(grid_level), pright, 1,                   &
135                             ar(nzb,nys-nbgp_local,nxl-nbgp_local), 1,         &
136                             type_yz(grid_level), pleft,  1,                   &
137                             comm2d, status, ierr )
138
139       ELSE
140
141!
142!--       In case of background communication switched on, exchange is done
143!--       either along x or along y
144          IF ( send_receive == 'lr'  .OR.  send_receive == 'al' )  THEN
145
146             IF ( .NOT. sendrecv_in_background )  THEN
147                req(1:4)  = 0
148                req_count = 0
149             ENDIF
150!
151!--          Send left boundary, receive right one (asynchronous)
152             CALL MPI_ISEND( ar(nzb,nys-nbgp_local,nxl),   1, type_yz(grid_level), &
153                             pleft, req_count, comm2d, req(req_count+1), ierr )
154             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz(grid_level), &
155                             pright, req_count, comm2d, req(req_count+2), ierr )
156!
157!--          Send right boundary, receive left one (asynchronous)
158             CALL MPI_ISEND( ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1,       &
159                             type_yz(grid_level), pright, req_count+1, comm2d, &
160                             req(req_count+3), ierr )
161             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,       &
162                             type_yz(grid_level), pleft,  req_count+1, comm2d, &
163                             req(req_count+4), ierr )
164
165             IF ( .NOT. sendrecv_in_background )  THEN
166                CALL MPI_WAITALL( 4, req, wait_stat, ierr )
167             ELSE
168                req_count = req_count + 4
169             ENDIF
170
171          ENDIF
172
173       ENDIF
174
175    ENDIF
176
177
178    IF ( pdims(2) == 1  .OR.  mg_switch_to_pe0 )  THEN
179!
180!--    One-dimensional decomposition along x, boundary values can be exchanged
181!--    within the PE memory
182       IF ( bc_ns_cyc )  THEN
183          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
184          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
185       ENDIF
186
187    ELSE
188
189       IF ( synchronous_exchange )  THEN
190!
191!--       Send front boundary, receive rear one (synchronous)
192          CALL MPI_SENDRECV(                                                   &
193              ar(nzb,nys,nxl-nbgp_local),   1, type_xz(grid_level), psouth, 0, &
194              ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz(grid_level), pnorth, 0, &
195              comm2d, status, ierr )
196!
197!--       Send rear boundary, receive front one (synchronous)
198          CALL MPI_SENDRECV( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1,       &
199                             type_xz(grid_level), pnorth, 1,                   &
200                             ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,       &
201                             type_xz(grid_level), psouth, 1,                   &
202                             comm2d, status, ierr )
203
204       ELSE
205
206!
207!--       In case of background communication switched on, exchange is done
208!--       either along x or along y
209          IF ( send_receive == 'ns'  .OR.  send_receive == 'al' )  THEN
210
211             IF ( .NOT. sendrecv_in_background )  THEN
212                req(1:4)  = 0
213                req_count = 0
214             ENDIF
215
216!
217!--          Send front boundary, receive rear one (asynchronous)
218             CALL MPI_ISEND( ar(nzb,nys,nxl-nbgp_local),   1, type_xz(grid_level), &
219                             psouth, req_count, comm2d, req(req_count+1), ierr )
220             CALL MPI_IRECV( ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz(grid_level), &
221                             pnorth, req_count, comm2d, req(req_count+2), ierr )
222!
223!--          Send rear boundary, receive front one (asynchronous)
224             CALL MPI_ISEND( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1,       &
225                             type_xz(grid_level), pnorth, req_count+1, comm2d, &
226                             req(req_count+3), ierr )
227             CALL MPI_IRECV( ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,       &
228                             type_xz(grid_level), psouth, req_count+1, comm2d, &
229                             req(req_count+4), ierr )
230
231             IF ( .NOT. sendrecv_in_background )  THEN
232                CALL MPI_WAITALL( 4, req, wait_stat, ierr )
233             ELSE
234                req_count = req_count + 4
235             ENDIF
236
237          ENDIF
238
239       ENDIF
240
241    ENDIF
242
243#else
244
245!
246!-- Lateral boundary conditions in the non-parallel case.
247!-- Case dependent, because in GPU mode still not all arrays are on device. This
248!-- workaround has to be removed later. Also, since PGI compiler 12.5 has problems
249!-- with array syntax, explicit loops are used.
250    IF ( bc_lr == 'cyclic' )  THEN
251       IF ( on_device )  THEN
252          !$acc kernels present( ar )
253          !$acc loop independent
254          DO  i = 0, nbgp_local-1
255             DO  j = nys-nbgp_local, nyn+nbgp_local
256                DO  k = nzb, nzt+1
257                   ar(k,j,nxl-nbgp_local+i) = ar(k,j,nxr-nbgp_local+1+i)
258                   ar(k,j,nxr+1+i)          = ar(k,j,nxl+i)
259                ENDDO
260             ENDDO
261          ENDDO
262          !$acc end kernels
263       ELSE
264          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
265          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
266       ENDIF
267    ENDIF
268
269    IF ( bc_ns == 'cyclic' )  THEN
270       IF ( on_device )  THEN
271          !$acc kernels present( ar )
272          DO  i = nxl-nbgp_local, nxr+nbgp_local
273             !$acc loop independent
274             DO  j = 0, nbgp_local-1
275                !$acc loop independent
276                DO  k = nzb, nzt+1
277                   ar(k,nys-nbgp_local+j,i) = ar(k,nyn-nbgp_local+1+j,i)
278                     ar(k,nyn+1+j,i)          = ar(k,nys+j,i)
279                ENDDO
280             ENDDO
281          ENDDO
282          !$acc end kernels
283       ELSE
284          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
285          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
286       ENDIF
287    ENDIF
288
289#endif
290    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'stop' )
291
292#endif
293 END SUBROUTINE exchange_horiz
294
295
296!------------------------------------------------------------------------------!
297! Description:
298! ------------
299!> @todo Missing subroutine description.
300!------------------------------------------------------------------------------!
301 SUBROUTINE exchange_horiz_int( ar, nbgp_local)
302
303    USE control_parameters,                                                    &
304        ONLY:  bc_lr, bc_lr_cyc, bc_ns, bc_ns_cyc
305                       
306    USE indices,                                                               &
307        ONLY:  nxl, nxr, nyn, nys, nzb, nzt
308       
309    USE kinds
310   
311    USE pegrid
312
313    IMPLICIT NONE
314
315
316    INTEGER(iwp) ::  nbgp_local  !< number of ghost points
317   
318    INTEGER(iwp), DIMENSION(nzb:nzt+1,nys-nbgp_local:nyn+nbgp_local,           &
319                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !< treated array
320
321#if ! defined( __check )
322
323#if defined( __parallel )
324    IF ( pdims(1) == 1 )  THEN
325!
326!--    One-dimensional decomposition along y, boundary values can be exchanged
327!--    within the PE memory
328       IF ( bc_lr_cyc )  THEN
329          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
330          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
331       ENDIF
332    ELSE
333!
334!--    Send left boundary, receive right one (synchronous)
335       CALL MPI_SENDRECV(                                                      &
336           ar(nzb,nys-nbgp_local,nxl),   1, type_yz_int, pleft,  0,            &
337           ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz_int, pright, 0,            &
338           comm2d, status, ierr )
339!
340!--    Send right boundary, receive left one (synchronous)
341       CALL MPI_SENDRECV(                                                      &
342           ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1, type_yz_int, pright, 1, &
343           ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1, type_yz_int, pleft,  1, &
344           comm2d, status, ierr )
345    ENDIF
346
347
348    IF ( pdims(2) == 1 )  THEN
349!
350!--    One-dimensional decomposition along x, boundary values can be exchanged
351!--    within the PE memory
352       IF ( bc_ns_cyc )  THEN
353          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
354          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
355       ENDIF
356
357    ELSE
358
359!
360!--    Send front boundary, receive rear one (synchronous)
361       CALL MPI_SENDRECV(                                                      &
362           ar(nzb,nys,nxl-nbgp_local),   1, type_xz_int, psouth, 0,            &
363           ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz_int, pnorth, 0,            &
364           comm2d, status, ierr )
365!
366!--    Send rear boundary, receive front one (synchronous)
367       CALL MPI_SENDRECV( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1,          &
368                          type_xz_int, pnorth, 1,                              &
369                          ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,          &
370                          type_xz_int, psouth, 1,                              &
371                          comm2d, status, ierr )
372
373    ENDIF
374
375#else
376
377    IF ( bc_lr == 'cyclic' )  THEN
378       ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
379       ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
380    ENDIF
381
382    IF ( bc_ns == 'cyclic' )  THEN
383       ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
384       ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
385    ENDIF
386
387#endif
388#endif
389
390
391 END SUBROUTINE exchange_horiz_int
Note: See TracBrowser for help on using the repository browser.