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

Last change on this file since 1763 was 1763, checked in by hellstea, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 9.2 KB
Line 
1!> @file exchange_horiz_2d.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: exchange_horiz_2d.f90 1763 2016-02-25 13:00:19Z hellstea $
26!
27! 1762 2016-02-25 12:31:13Z hellstea
28! Introduction of nested domain feature
29!
30! 1682 2015-10-07 23:56:08Z knoop
31! Code annotations made doxygen readable
32!
33! 1348 2014-03-27 18:01:03Z raasch
34! bugfix: bc_lr_cyc and bc_ns_cyc added to ONLY-list
35!
36! 1320 2014-03-20 08:40:49Z raasch
37! ONLY-attribute added to USE-statements,
38! kind-parameters added to all INTEGER and REAL declaration statements,
39! kinds are defined in new module kinds,
40! revision history before 2012 removed,
41! comment fields (!:) to be used for variable explanations added to
42! all variable declaration statements
43!
44! 1092 2013-02-02 11:24:22Z raasch
45! unused variables removed
46!
47! 1036 2012-10-22 13:43:42Z raasch
48! code put under GPL (PALM 3.9)
49!
50! 841 2012-02-28 12:29:49Z maronga
51! Excluded routine from compilation of namelist_file_check
52!
53! Revision 1.1  1998/01/23 09:58:21  raasch
54! Initial revision
55!
56!
57! Description:
58! ------------
59!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
60!> boundary conditions, respectively, for 2D-arrays.
61!------------------------------------------------------------------------------!
62 SUBROUTINE exchange_horiz_2d( ar )
63 
64
65    USE control_parameters,                                                    &
66        ONLY :  bc_lr_cyc, bc_ns_cyc, inflow_l, inflow_n, inflow_r, inflow_s,  &
67                nest_bound_l, nest_bound_n, nest_bound_r, nest_bound_s,        &
68                outflow_l, outflow_n, outflow_r, outflow_s
69               
70    USE cpulog,                                                                &
71        ONLY :  cpu_log, log_point_s
72       
73    USE indices,                                                               &
74        ONLY :  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg
75       
76    USE kinds
77   
78    USE pegrid
79
80    IMPLICIT NONE
81
82
83    INTEGER(iwp) :: i  !<
84   
85    REAL(wp) ::  ar(nysg:nyng,nxlg:nxrg)  !<
86   
87
88#if ! defined( __check )
89    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
90
91#if defined( __parallel )
92
93!
94!-- Exchange of lateral boundary values for parallel computers
95    IF ( pdims(1) == 1 )  THEN
96
97!
98!--    One-dimensional decomposition along y, boundary values can be exchanged
99!--    within the PE memory
100       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
101       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
102
103    ELSE
104!
105!--    Send left boundary, receive right one
106
107       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y, pleft,  0,                 &
108                          ar(nysg,nxr+1), 1, type_y, pright, 0,               &
109                          comm2d, status, ierr )
110!
111!--    Send right boundary, receive left one
112       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y, pright,  1,         &
113                          ar(nysg,nxlg), 1, type_y, pleft,   1,               &
114                          comm2d, status, ierr )
115                         
116     
117    ENDIF
118
119    IF ( pdims(2) == 1 )  THEN
120!
121!--    One-dimensional decomposition along x, boundary values can be exchanged
122!--    within the PE memory
123       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
124       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
125
126    ELSE
127!
128!--    Send front boundary, receive rear one
129
130       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x, psouth, 0,                 &         
131                          ar(nyn+1,nxlg), 1, type_x, pnorth, 0,               &
132                          comm2d, status, ierr )
133!
134!--    Send rear boundary, receive front one
135       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x, pnorth, 1,          &
136                          ar(nysg,nxlg), 1, type_x, psouth, 1,                &
137                          comm2d, status, ierr )
138
139    ENDIF
140
141#else
142
143!
144!-- Lateral boundary conditions in the non-parallel case
145    IF ( bc_lr_cyc )  THEN
146       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
147       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
148    ENDIF
149
150    IF ( bc_ns_cyc )  THEN
151       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
152       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
153    ENDIF
154
155
156#endif
157
158!
159!-- Neumann-conditions at inflow/outflow/nested boundaries
160    IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
161       DO  i = nbgp, 1, -1
162         ar(:,nxl-i) = ar(:,nxl)
163       ENDDO
164    ENDIF
165    IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
166       DO  i = 1, nbgp
167          ar(:,nxr+i) = ar(:,nxr)
168       ENDDO
169    ENDIF
170    IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
171       DO  i = nbgp, 1, -1
172         ar(nys-i,:) = ar(nys,:)
173       ENDDO
174    ENDIF
175    IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
176       DO  i = 1, nbgp
177         ar(nyn+i,:) = ar(nyn,:)
178       ENDDO
179    ENDIF
180
181    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
182
183#endif
184 END SUBROUTINE exchange_horiz_2d
185
186
187
188!------------------------------------------------------------------------------!
189! Description:
190! ------------
191!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
192!> boundary conditions, respectively, for 2D integer arrays.
193!------------------------------------------------------------------------------!
194 
195 SUBROUTINE exchange_horiz_2d_int( ar )
196
197
198    USE control_parameters,                                                    &
199        ONLY:  bc_lr_cyc, bc_ns_cyc, nest_bound_l, nest_bound_n, nest_bound_r, &
200               nest_bound_s
201       
202    USE cpulog,                                                                &
203        ONLY:  cpu_log, log_point_s
204       
205    USE indices,                                                               &
206        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg
207       
208    USE kinds
209   
210    USE pegrid
211
212    IMPLICIT NONE
213
214    INTEGER(iwp) ::  i
215    INTEGER(iwp) ::  ar(nysg:nyng,nxlg:nxrg)  !<
216
217#if ! defined( __check )
218    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
219
220#if defined( __parallel )
221
222!
223!-- Exchange of lateral boundary values for parallel computers
224    IF ( pdims(1) == 1 )  THEN
225
226!
227!--    One-dimensional decomposition along y, boundary values can be exchanged
228!--    within the PE memory
229       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
230       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
231
232
233    ELSE
234!
235!--    Send left boundary, receive right one
236       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y_int, pleft,  0,             &
237                          ar(nysg,nxr+1), 1, type_y_int, pright, 0,           &
238                          comm2d, status, ierr )
239!
240!--    Send right boundary, receive left one
241       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y_int, pright,  1,     &
242                          ar(nysg,nxlg), 1, type_y_int, pleft,   1,           &
243                          comm2d, status, ierr )
244
245    ENDIF
246
247    IF ( pdims(2) == 1 )  THEN
248!
249!--    One-dimensional decomposition along x, boundary values can be exchanged
250!--    within the PE memory
251       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
252       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
253
254
255    ELSE
256!
257!--    Send front boundary, receive rear one
258       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x_int, psouth, 0,             &
259                          ar(nyn+1,nxlg), 1, type_x_int, pnorth, 0,           &
260                          comm2d, status, ierr )                         
261
262!
263!--    Send rear boundary, receive front one
264       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x_int, pnorth, 1,      &
265                          ar(nysg,nxlg), 1, type_x_int, psouth, 1,            &
266                          comm2d, status, ierr )
267
268    ENDIF
269
270#else
271
272!
273!-- Lateral boundary conditions in the non-parallel case
274    IF ( bc_lr_cyc )  THEN
275       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
276       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
277    ENDIF
278
279    IF ( bc_ns_cyc )  THEN
280       ar(nysg:nys-1,:) = ar(nyn+1-nbgp:nyn,:)
281       ar(nyn+1:nyng,:) = ar(nys:nys-1+nbgp,:)
282    ENDIF
283
284#endif
285!
286!-- Neumann-conditions at inflow/outflow/nested boundaries
287    IF ( nest_bound_l )  THEN
288       DO  i = nbgp, 1, -1
289         ar(:,nxl-i) = ar(:,nxl)
290       ENDDO
291    ENDIF
292    IF ( nest_bound_r )  THEN
293       DO  i = 1, nbgp
294          ar(:,nxr+i) = ar(:,nxr)
295       ENDDO
296    ENDIF
297    IF ( nest_bound_s )  THEN
298       DO  i = nbgp, 1, -1
299         ar(nys-i,:) = ar(nys,:)
300       ENDDO
301    ENDIF
302    IF ( nest_bound_n )  THEN
303       DO  i = 1, nbgp
304         ar(nyn+i,:) = ar(nyn,:)
305       ENDDO
306    ENDIF
307
308    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
309
310#endif
311 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.