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

Last change on this file since 1538 was 1349, checked in by raasch, 10 years ago

last commit documented

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