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

Last change on this file since 1036 was 1036, checked in by raasch, 12 years ago

code has been put under the GNU General Public License (v3)

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