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

Last change on this file since 1329 was 1321, checked in by raasch, 10 years ago

last commit documented

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