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

Last change on this file since 1308 was 1093, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 7.7 KB
RevLine 
[1]1 SUBROUTINE exchange_horiz_2d( ar )
2
[1036]3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
[484]20! Current revisions:
[1]21! -----------------
[1093]22!
[1]23!
24! Former revisions:
25! -----------------
[3]26! $Id: exchange_horiz_2d.f90 1093 2013-02-02 12:58:49Z fricke $
[77]27!
[1093]28! 1092 2013-02-02 11:24:22Z raasch
29! unused variables removed
30!
[1037]31! 1036 2012-10-22 13:43:42Z raasch
32! code put under GPL (PALM 3.9)
33!
[842]34! 841 2012-02-28 12:29:49Z maronga
35! Excluded routine from compilation of namelist_file_check
36!
[708]37! 707 2011-03-29 11:39:40Z raasch
38! bc_lr/ns replaced by bc_lr/ns_cyc
39!
[703]40! 702 2011-03-24 19:33:15Z suehring
41! Bugfix in declaration of ar in exchange_horiz_2d_int and number of MPI-blocks
42! in MPI_SENDRECV().
43!
[668]44! 667 2010-12-23 12:06:00Z suehring/gryschka
45! Dynamic exchange of ghost points with nbgp, which depends on the advection
46! scheme. Exchange between left and right PEs is now done with MPI-vectors.
47!
[77]48! 73 2007-03-20 08:33:14Z raasch
49! Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary
50! conditions
51!
[3]52! RCS Log replace by Id keyword, revision history cleaned up
53!
[1]54! Revision 1.9  2006/05/12 19:15:52  letzel
55! MPI_REAL replaced by MPI_INTEGER in exchange_horiz_2d_int
56!
57! Revision 1.1  1998/01/23 09:58:21  raasch
58! Initial revision
59!
60!
61! Description:
62! ------------
63! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
64! boundary conditions, respectively, for 2D-arrays.
65!------------------------------------------------------------------------------!
66
67    USE control_parameters
68    USE cpulog
69    USE indices
70    USE interfaces
71    USE pegrid
72
73    IMPLICIT NONE
74
[841]75
[667]76    REAL ::  ar(nysg:nyng,nxlg:nxrg)
77    INTEGER :: i
[1]78
[841]79#if ! defined( __check )
[1]80    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
81
82#if defined( __parallel )
83
84!
85!-- Exchange of lateral boundary values for parallel computers
86    IF ( pdims(1) == 1 )  THEN
87
88!
89!--    One-dimensional decomposition along y, boundary values can be exchanged
90!--    within the PE memory
[702]91       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
92       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]93
94    ELSE
95!
96!--    Send left boundary, receive right one
[667]97
[702]98       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y, pleft,  0,                 &
99                          ar(nysg,nxr+1), 1, type_y, pright, 0,               &
[1]100                          comm2d, status, ierr )
101!
102!--    Send right boundary, receive left one
[702]103       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y, pright,  1,         &
104                          ar(nysg,nxlg), 1, type_y, pleft,   1,               &
[1]105                          comm2d, status, ierr )
[702]106                         
107     
[1]108    ENDIF
109
110    IF ( pdims(2) == 1 )  THEN
111!
112!--    One-dimensional decomposition along x, boundary values can be exchanged
113!--    within the PE memory
[702]114       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
115       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
[1]116
117    ELSE
118!
119!--    Send front boundary, receive rear one
[667]120
[702]121       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x, psouth, 0,                 &         
122                          ar(nyn+1,nxlg), 1, type_x, pnorth, 0,               &
[1]123                          comm2d, status, ierr )
124!
125!--    Send rear boundary, receive front one
[702]126       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x, pnorth, 1,          &
127                          ar(nysg,nxlg), 1, type_x, psouth, 1,                &
[1]128                          comm2d, status, ierr )
[667]129
[1]130    ENDIF
131
132#else
133
134!
135!-- Lateral boundary conditions in the non-parallel case
[707]136    IF ( bc_lr_cyc )  THEN
[702]137       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
138       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]139    ENDIF
140
[707]141    IF ( bc_ns_cyc )  THEN
[702]142       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
143       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
[1]144    ENDIF
145
[667]146
[1]147#endif
148
[73]149!
150!-- Neumann-conditions at inflow/outflow in case of non-cyclic boundary
151!-- conditions
[667]152    IF ( inflow_l .OR. outflow_l )  THEN
153       DO i=nbgp, 1, -1
154         ar(:,nxl-i) = ar(:,nxl)
155       END DO
156    END IF
157    IF ( inflow_r .OR. outflow_r )  THEN
158       DO i=1, nbgp
159          ar(:,nxr+i) = ar(:,nxr)
160       END DO
161    END IF
162    IF ( inflow_s .OR. outflow_s )  THEN
163       DO i=nbgp, 1, -1
164         ar(nys-i,:) = ar(nys,:)
165       END DO
166    END IF
167    IF ( inflow_n .OR. outflow_n )  THEN
168       DO i=1, nbgp
169         ar(nyn+i,:) = ar(nyn,:)
170       END DO
171    END IF
[1]172    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
173
[841]174#endif
[1]175 END SUBROUTINE exchange_horiz_2d
176
177
178
179 SUBROUTINE exchange_horiz_2d_int( ar )
180
181!------------------------------------------------------------------------------!
182! Description:
183! ------------
184! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
185! boundary conditions, respectively, for 2D integer arrays.
186!------------------------------------------------------------------------------!
187
188    USE control_parameters
189    USE cpulog
190    USE indices
191    USE interfaces
192    USE pegrid
193
194    IMPLICIT NONE
195
[702]196    INTEGER ::  ar(nysg:nyng,nxlg:nxrg)
[1]197
[841]198#if ! defined( __check )
[1]199    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
200
201#if defined( __parallel )
202
203!
204!-- Exchange of lateral boundary values for parallel computers
205    IF ( pdims(1) == 1 )  THEN
206
207!
208!--    One-dimensional decomposition along y, boundary values can be exchanged
209!--    within the PE memory
[702]210       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
211       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]212
[702]213
[1]214    ELSE
215!
216!--    Send left boundary, receive right one
[702]217       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y_int, pleft,  0,             &
218                          ar(nysg,nxr+1), 1, type_y_int, pright, 0,           &
[1]219                          comm2d, status, ierr )
220!
221!--    Send right boundary, receive left one
[702]222       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y_int, pright,  1,     &
223                          ar(nysg,nxlg), 1, type_y_int, pleft,   1,           &
[1]224                          comm2d, status, ierr )
[667]225
[1]226    ENDIF
227
228    IF ( pdims(2) == 1 )  THEN
229!
230!--    One-dimensional decomposition along x, boundary values can be exchanged
231!--    within the PE memory
[667]232       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
233       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
[1]234
[667]235
[1]236    ELSE
237!
238!--    Send front boundary, receive rear one
[702]239       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x_int, psouth, 0,             &
240                          ar(nyn+1,nxlg), 1, type_x_int, pnorth, 0,           &
241                          comm2d, status, ierr )                         
[667]242
[1]243!
244!--    Send rear boundary, receive front one
[702]245       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x_int, pnorth, 1,      &
246                          ar(nysg,nxlg), 1, type_x_int, psouth, 1,            &
[1]247                          comm2d, status, ierr )
[667]248
[1]249    ENDIF
250
251#else
252
253!
254!-- Lateral boundary conditions in the non-parallel case
[707]255    IF ( bc_lr_cyc )  THEN
[702]256       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
257       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
[1]258    ENDIF
259
[707]260    IF ( bc_ns_cyc )  THEN
[667]261       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
262       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
[1]263    ENDIF
264
265#endif
266    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
267
[841]268#endif
[1]269 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.