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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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