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

Last change on this file since 2701 was 2696, checked in by kanani, 7 years ago

Merge of branch palm4u into trunk

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