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

Last change on this file since 1762 was 1762, checked in by hellstea, 8 years ago

Introduction of nested domain system

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