source: palm/trunk/SOURCE/exchange_horiz_2d.f90 @ 2101

Last change on this file since 2101 was 2101, checked in by suehring, 7 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 11.1 KB
RevLine 
[1682]1!> @file exchange_horiz_2d.f90
[2000]2!------------------------------------------------------------------------------!
[1036]3! This file is part of PALM.
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
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[484]20! Current revisions:
[1]21! -----------------
[1683]22!
[2001]23!
[1321]24! Former revisions:
25! -----------------
26! $Id: exchange_horiz_2d.f90 2101 2017-01-05 16:42:31Z suehring $
27!
[2001]28! 2000 2016-08-20 18:09:15Z knoop
29! Forced header and separation lines into 80 columns
30!
[1969]31! 1968 2016-07-18 12:01:49Z suehring
32! 2D-INTEGER exchange adopted for different multigrid level
33!
[1933]34! 1818 2016-04-06 15:53:27Z maronga
35! Initial version of purely vertical nesting introduced.
36!
[1805]37! 1804 2016-04-05 16:30:18Z maronga
38! Removed code for parameter file check (__check)
39!
[1763]40! 1762 2016-02-25 12:31:13Z hellstea
41! Introduction of nested domain feature
42!
[1683]43! 1682 2015-10-07 23:56:08Z knoop
44! Code annotations made doxygen readable
45!
[1349]46! 1348 2014-03-27 18:01:03Z raasch
47! bugfix: bc_lr_cyc and bc_ns_cyc added to ONLY-list
48!
[1321]49! 1320 2014-03-20 08:40:49Z raasch
[1320]50! ONLY-attribute added to USE-statements,
51! kind-parameters added to all INTEGER and REAL declaration statements,
52! kinds are defined in new module kinds,
53! revision history before 2012 removed,
54! comment fields (!:) to be used for variable explanations added to
55! all variable declaration statements
[1]56!
[1093]57! 1092 2013-02-02 11:24:22Z raasch
58! unused variables removed
59!
[1037]60! 1036 2012-10-22 13:43:42Z raasch
61! code put under GPL (PALM 3.9)
62!
[842]63! 841 2012-02-28 12:29:49Z maronga
64! Excluded routine from compilation of namelist_file_check
65!
[1]66! Revision 1.1  1998/01/23 09:58:21  raasch
67! Initial revision
68!
69!
70! Description:
71! ------------
[1682]72!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
73!> boundary conditions, respectively, for 2D-arrays.
[1]74!------------------------------------------------------------------------------!
[1682]75 SUBROUTINE exchange_horiz_2d( ar )
76 
[1]77
[1320]78    USE control_parameters,                                                    &
[1348]79        ONLY :  bc_lr_cyc, bc_ns_cyc, inflow_l, inflow_n, inflow_r, inflow_s,  &
[1762]80                nest_bound_l, nest_bound_n, nest_bound_r, nest_bound_s,        &
[1348]81                outflow_l, outflow_n, outflow_r, outflow_s
[1320]82               
83    USE cpulog,                                                                &
84        ONLY :  cpu_log, log_point_s
85       
86    USE indices,                                                               &
87        ONLY :  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg
88       
89    USE kinds
90   
[1]91    USE pegrid
92
[1933]93    USE pmc_interface,                                                         &
94        ONLY : nesting_mode
95
96
[1]97    IMPLICIT NONE
98
[841]99
[1682]100    INTEGER(iwp) :: i  !<
[1320]101   
[1682]102    REAL(wp) ::  ar(nysg:nyng,nxlg:nxrg)  !<
[1320]103   
[1]104
105    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
106
107#if defined( __parallel )
108
109!
110!-- Exchange of lateral boundary values for parallel computers
111    IF ( pdims(1) == 1 )  THEN
112
113!
114!--    One-dimensional decomposition along y, boundary values can be exchanged
115!--    within the PE memory
[702]116       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
117       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]118
119    ELSE
120!
121!--    Send left boundary, receive right one
[667]122
[702]123       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y, pleft,  0,                 &
124                          ar(nysg,nxr+1), 1, type_y, pright, 0,               &
[1]125                          comm2d, status, ierr )
126!
127!--    Send right boundary, receive left one
[702]128       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y, pright,  1,         &
129                          ar(nysg,nxlg), 1, type_y, pleft,   1,               &
[1]130                          comm2d, status, ierr )
[702]131                         
132     
[1]133    ENDIF
134
135    IF ( pdims(2) == 1 )  THEN
136!
137!--    One-dimensional decomposition along x, boundary values can be exchanged
138!--    within the PE memory
[702]139       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
140       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
[1]141
142    ELSE
143!
144!--    Send front boundary, receive rear one
[667]145
[702]146       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x, psouth, 0,                 &         
147                          ar(nyn+1,nxlg), 1, type_x, pnorth, 0,               &
[1]148                          comm2d, status, ierr )
149!
150!--    Send rear boundary, receive front one
[702]151       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x, pnorth, 1,          &
152                          ar(nysg,nxlg), 1, type_x, psouth, 1,                &
[1]153                          comm2d, status, ierr )
[667]154
[1]155    ENDIF
156
157#else
158
159!
160!-- Lateral boundary conditions in the non-parallel case
[707]161    IF ( bc_lr_cyc )  THEN
[702]162       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
163       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]164    ENDIF
165
[707]166    IF ( bc_ns_cyc )  THEN
[702]167       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
168       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
[1]169    ENDIF
170
[667]171
[1]172#endif
173
[73]174!
[1762]175!-- Neumann-conditions at inflow/outflow/nested boundaries
[1933]176    IF ( nesting_mode /= 'vertical' )  THEN
177       IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
178          DO  i = nbgp, 1, -1
179             ar(:,nxl-i) = ar(:,nxl)
180          ENDDO
181       ENDIF
182       IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
183          DO  i = 1, nbgp
184             ar(:,nxr+i) = ar(:,nxr)
185          ENDDO
186       ENDIF
187       IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
188          DO  i = nbgp, 1, -1
189             ar(nys-i,:) = ar(nys,:)
190          ENDDO
191       ENDIF
192       IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
193          DO  i = 1, nbgp
194             ar(nyn+i,:) = ar(nyn,:)
195          ENDDO
196       ENDIF
[1762]197    ENDIF
198
[1]199    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
200
201 END SUBROUTINE exchange_horiz_2d
202
203
204
205!------------------------------------------------------------------------------!
206! Description:
207! ------------
[1682]208!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
209!> boundary conditions, respectively, for 2D integer arrays.
[1]210!------------------------------------------------------------------------------!
[1682]211 
[1968]212 SUBROUTINE exchange_horiz_2d_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nbgp_local )
[1]213
[1682]214
[1320]215    USE control_parameters,                                                    &
[1968]216        ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, nest_bound_l, nest_bound_n,   &
217               nest_bound_r, nest_bound_s
[1320]218       
219    USE cpulog,                                                                &
220        ONLY:  cpu_log, log_point_s
[1968]221               
[1320]222    USE kinds
223   
[1]224    USE pegrid
225
226    IMPLICIT NONE
227
[1968]228    INTEGER(iwp) ::  i           !< dummy index to zero-gradient conditions at in/outflow boundaries
229    INTEGER(iwp) ::  nxl_l       !< local index bound at current grid level, left side
230    INTEGER(iwp) ::  nxr_l       !< local index bound at current grid level, right side
231    INTEGER(iwp) ::  nyn_l       !< local index bound at current grid level, north side
232    INTEGER(iwp) ::  nys_l       !< local index bound at current grid level, south side
233    INTEGER(iwp) ::  nbgp_local  !< number of ghost layers to be exchanged
[1]234
[1968]235    INTEGER(iwp), DIMENSION(nys_l-nbgp_local:nyn_l+nbgp_local,                 &
236                            nxl_l-nbgp_local:nxr_l+nbgp_local) ::  ar  !< treated array
237
[1]238    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
239
240#if defined( __parallel )
241
242!
243!-- Exchange of lateral boundary values for parallel computers
244    IF ( pdims(1) == 1 )  THEN
245
246!
247!--    One-dimensional decomposition along y, boundary values can be exchanged
248!--    within the PE memory
[1968]249       ar(:,nxl_l-nbgp_local:nxl_l-1) = ar(:,nxr_l-nbgp_local+1:nxr_l)
250       ar(:,nxr_l+1:nxr_l+nbgp_local) = ar(:,nxl_l:nxl_l+nbgp_local-1)
[1]251
252    ELSE
253!
254!--    Send left boundary, receive right one
[1968]255       CALL MPI_SENDRECV( ar(nys_l-nbgp_local,nxl_l),   1,                     &
256                          type_y_int(grid_level), pleft,  0,                   &
257                          ar(nys_l-nbgp_local,nxr_l+1), 1,                     &
258                          type_y_int(grid_level), pright, 0,                   &
[1]259                          comm2d, status, ierr )
260!
261!--    Send right boundary, receive left one
[1968]262       CALL MPI_SENDRECV( ar(nys_l-nbgp_local,nxr_l+1-nbgp_local), 1,          &
263                          type_y_int(grid_level), pright, 1,                   &
264                          ar(nys_l-nbgp_local,nxl_l-nbgp_local),   1,          & 
265                          type_y_int(grid_level), pleft,  1,                   &
266                          comm2d, status, ierr )                         
[667]267
[1]268    ENDIF
269
270    IF ( pdims(2) == 1 )  THEN
271!
272!--    One-dimensional decomposition along x, boundary values can be exchanged
273!--    within the PE memory
[1968]274       ar(nys_l-nbgp_local:nys_l-1,:) = ar(nyn_l+1-nbgp_local:nyn_l,:)
275       ar(nyn_l+1:nyn_l+nbgp_local,:) = ar(nys_l:nys_l-1+nbgp_local,:)
[1]276
[667]277
[1]278    ELSE
279!
280!--    Send front boundary, receive rear one
[1968]281       CALL MPI_SENDRECV( ar(nys_l,nxl_l-nbgp_local),   1,                    &
282                          type_x_int(grid_level), psouth, 0,                  &
283                          ar(nyn_l+1,nxl_l-nbgp_local), 1,                    &
284                          type_x_int(grid_level), pnorth, 0,                  &
[702]285                          comm2d, status, ierr )                         
[667]286
[1]287!
288!--    Send rear boundary, receive front one
[1968]289       CALL MPI_SENDRECV( ar(nyn_l+1-nbgp_local,nxl_l-nbgp_local), 1,         &
290                          type_x_int(grid_level), pnorth, 1,                  &
291                          ar(nys_l-nbgp_local,nxl_l-nbgp_local),   1,         &
292                          type_x_int(grid_level), psouth, 1,                  &
[1]293                          comm2d, status, ierr )
[667]294
[1]295    ENDIF
296
297#else
298
299!
300!-- Lateral boundary conditions in the non-parallel case
[707]301    IF ( bc_lr_cyc )  THEN
[1968]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)
[1]304    ENDIF
305
[707]306    IF ( bc_ns_cyc )  THEN
[1968]307       ar(nys_l-nbgp_local:nys_l-1,:) = ar(nyn_l+1-nbgp_local:nyn_l,:)
308       ar(nyn_l+1:nyn_l+nbgp_local,:) = ar(nys_l:nys_l-1+nbgp_local,:)
[1]309    ENDIF
310
311#endif
[1762]312!
313!-- Neumann-conditions at inflow/outflow/nested boundaries
314    IF ( nest_bound_l )  THEN
[1968]315       DO  i = nbgp_local, 1, -1
316         ar(:,nxl_l-i) = ar(:,nxl_l)
[1762]317       ENDDO
318    ENDIF
319    IF ( nest_bound_r )  THEN
[1968]320       DO  i = 1, nbgp_local
321          ar(:,nxr_l+i) = ar(:,nxr_l)
[1762]322       ENDDO
323    ENDIF
324    IF ( nest_bound_s )  THEN
[1968]325       DO  i = nbgp_local, 1, -1
326         ar(nys_l-i,:) = ar(nys_l,:)
[1762]327       ENDDO
328    ENDIF
329    IF ( nest_bound_n )  THEN
[1968]330       DO  i = 1, nbgp_local
331         ar(nyn_l+i,:) = ar(nyn_l,:)
[1762]332       ENDDO
333    ENDIF
334
[1]335    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
336
337 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.