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

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