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

Last change on this file since 1968 was 1968, checked in by suehring, 8 years ago

PE-wise reading of topography file

  • Property svn:keywords set to Id
File size: 11.0 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-2016 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21! 2D-INTEGER exchange adopted for different multigrid level
22!
23! Former revisions:
24! -----------------
25! $Id: exchange_horiz_2d.f90 1968 2016-07-18 12:01:49Z suehring $
26!
27! 1818 2016-04-06 15:53:27Z maronga
28! Initial version of purely vertical nesting introduced.
29!
30! 1804 2016-04-05 16:30:18Z maronga
31! Removed code for parameter file check (__check)
32!
33! 1762 2016-02-25 12:31:13Z hellstea
34! Introduction of nested domain feature
35!
36! 1682 2015-10-07 23:56:08Z knoop
37! Code annotations made doxygen readable
38!
39! 1348 2014-03-27 18:01:03Z raasch
40! bugfix: bc_lr_cyc and bc_ns_cyc added to ONLY-list
41!
42! 1320 2014-03-20 08:40:49Z raasch
43! ONLY-attribute added to USE-statements,
44! kind-parameters added to all INTEGER and REAL declaration statements,
45! kinds are defined in new module kinds,
46! revision history before 2012 removed,
47! comment fields (!:) to be used for variable explanations added to
48! all variable declaration statements
49!
50! 1092 2013-02-02 11:24:22Z raasch
51! unused variables removed
52!
53! 1036 2012-10-22 13:43:42Z raasch
54! code put under GPL (PALM 3.9)
55!
56! 841 2012-02-28 12:29:49Z maronga
57! Excluded routine from compilation of namelist_file_check
58!
59! Revision 1.1  1998/01/23 09:58:21  raasch
60! Initial revision
61!
62!
63! Description:
64! ------------
65!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
66!> boundary conditions, respectively, for 2D-arrays.
67!------------------------------------------------------------------------------!
68 SUBROUTINE exchange_horiz_2d( ar )
69 
70
71    USE control_parameters,                                                    &
72        ONLY :  bc_lr_cyc, bc_ns_cyc, inflow_l, inflow_n, inflow_r, inflow_s,  &
73                nest_bound_l, nest_bound_n, nest_bound_r, nest_bound_s,        &
74                outflow_l, outflow_n, outflow_r, outflow_s
75               
76    USE cpulog,                                                                &
77        ONLY :  cpu_log, log_point_s
78       
79    USE indices,                                                               &
80        ONLY :  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg
81       
82    USE kinds
83   
84    USE pegrid
85
86    USE pmc_interface,                                                         &
87        ONLY : nesting_mode
88
89
90    IMPLICIT NONE
91
92
93    INTEGER(iwp) :: i  !<
94   
95    REAL(wp) ::  ar(nysg:nyng,nxlg:nxrg)  !<
96   
97
98    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
99
100#if defined( __parallel )
101
102!
103!-- Exchange of lateral boundary values for parallel computers
104    IF ( pdims(1) == 1 )  THEN
105
106!
107!--    One-dimensional decomposition along y, boundary values can be exchanged
108!--    within the PE memory
109       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
110       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
111
112    ELSE
113!
114!--    Send left boundary, receive right one
115
116       CALL MPI_SENDRECV( ar(nysg,nxl), 1, type_y, pleft,  0,                 &
117                          ar(nysg,nxr+1), 1, type_y, pright, 0,               &
118                          comm2d, status, ierr )
119!
120!--    Send right boundary, receive left one
121       CALL MPI_SENDRECV( ar(nysg,nxr+1-nbgp), 1, type_y, pright,  1,         &
122                          ar(nysg,nxlg), 1, type_y, pleft,   1,               &
123                          comm2d, status, ierr )
124                         
125     
126    ENDIF
127
128    IF ( pdims(2) == 1 )  THEN
129!
130!--    One-dimensional decomposition along x, boundary values can be exchanged
131!--    within the PE memory
132       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
133       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
134
135    ELSE
136!
137!--    Send front boundary, receive rear one
138
139       CALL MPI_SENDRECV( ar(nys,nxlg), 1, type_x, psouth, 0,                 &         
140                          ar(nyn+1,nxlg), 1, type_x, pnorth, 0,               &
141                          comm2d, status, ierr )
142!
143!--    Send rear boundary, receive front one
144       CALL MPI_SENDRECV( ar(nyn+1-nbgp,nxlg), 1, type_x, pnorth, 1,          &
145                          ar(nysg,nxlg), 1, type_x, psouth, 1,                &
146                          comm2d, status, ierr )
147
148    ENDIF
149
150#else
151
152!
153!-- Lateral boundary conditions in the non-parallel case
154    IF ( bc_lr_cyc )  THEN
155       ar(:,nxlg:nxl-1) = ar(:,nxr-nbgp+1:nxr)
156       ar(:,nxr+1:nxrg) = ar(:,nxl:nxl+nbgp-1)
157    ENDIF
158
159    IF ( bc_ns_cyc )  THEN
160       ar(nysg:nys-1,:) = ar(nyn-nbgp+1:nyn,:)
161       ar(nyn+1:nyng,:) = ar(nys:nys+nbgp-1,:)
162    ENDIF
163
164
165#endif
166
167!
168!-- Neumann-conditions at inflow/outflow/nested boundaries
169    IF ( nesting_mode /= 'vertical' )  THEN
170       IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
171          DO  i = nbgp, 1, -1
172             ar(:,nxl-i) = ar(:,nxl)
173          ENDDO
174       ENDIF
175       IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
176          DO  i = 1, nbgp
177             ar(:,nxr+i) = ar(:,nxr)
178          ENDDO
179       ENDIF
180       IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
181          DO  i = nbgp, 1, -1
182             ar(nys-i,:) = ar(nys,:)
183          ENDDO
184       ENDIF
185       IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
186          DO  i = 1, nbgp
187             ar(nyn+i,:) = ar(nyn,:)
188          ENDDO
189       ENDIF
190    ENDIF
191
192    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
193
194 END SUBROUTINE exchange_horiz_2d
195
196
197
198!------------------------------------------------------------------------------!
199! Description:
200! ------------
201!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
202!> boundary conditions, respectively, for 2D integer arrays.
203!------------------------------------------------------------------------------!
204 
205 SUBROUTINE exchange_horiz_2d_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nbgp_local )
206
207
208    USE control_parameters,                                                    &
209        ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, nest_bound_l, nest_bound_n,   &
210               nest_bound_r, nest_bound_s
211       
212    USE cpulog,                                                                &
213        ONLY:  cpu_log, log_point_s
214               
215    USE kinds
216   
217    USE pegrid
218
219    IMPLICIT NONE
220
221    INTEGER(iwp) ::  i           !< dummy index to zero-gradient conditions at in/outflow boundaries
222    INTEGER(iwp) ::  nxl_l       !< local index bound at current grid level, left side
223    INTEGER(iwp) ::  nxr_l       !< local index bound at current grid level, right side
224    INTEGER(iwp) ::  nyn_l       !< local index bound at current grid level, north side
225    INTEGER(iwp) ::  nys_l       !< local index bound at current grid level, south side
226    INTEGER(iwp) ::  nbgp_local  !< number of ghost layers to be exchanged
227
228    INTEGER(iwp), DIMENSION(nys_l-nbgp_local:nyn_l+nbgp_local,                 &
229                            nxl_l-nbgp_local:nxr_l+nbgp_local) ::  ar  !< treated array
230
231    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
232
233#if defined( __parallel )
234
235!
236!-- Exchange of lateral boundary values for parallel computers
237    IF ( pdims(1) == 1 )  THEN
238
239!
240!--    One-dimensional decomposition along y, boundary values can be exchanged
241!--    within the PE memory
242       ar(:,nxl_l-nbgp_local:nxl_l-1) = ar(:,nxr_l-nbgp_local+1:nxr_l)
243       ar(:,nxr_l+1:nxr_l+nbgp_local) = ar(:,nxl_l:nxl_l+nbgp_local-1)
244
245    ELSE
246!
247!--    Send left boundary, receive right one
248       CALL MPI_SENDRECV( ar(nys_l-nbgp_local,nxl_l),   1,                     &
249                          type_y_int(grid_level), pleft,  0,                   &
250                          ar(nys_l-nbgp_local,nxr_l+1), 1,                     &
251                          type_y_int(grid_level), pright, 0,                   &
252                          comm2d, status, ierr )
253!
254!--    Send right boundary, receive left one
255       CALL MPI_SENDRECV( ar(nys_l-nbgp_local,nxr_l+1-nbgp_local), 1,          &
256                          type_y_int(grid_level), pright, 1,                   &
257                          ar(nys_l-nbgp_local,nxl_l-nbgp_local),   1,          & 
258                          type_y_int(grid_level), pleft,  1,                   &
259                          comm2d, status, ierr )                         
260
261    ENDIF
262
263    IF ( pdims(2) == 1 )  THEN
264!
265!--    One-dimensional decomposition along x, boundary values can be exchanged
266!--    within the PE memory
267       ar(nys_l-nbgp_local:nys_l-1,:) = ar(nyn_l+1-nbgp_local:nyn_l,:)
268       ar(nyn_l+1:nyn_l+nbgp_local,:) = ar(nys_l:nys_l-1+nbgp_local,:)
269
270
271    ELSE
272!
273!--    Send front boundary, receive rear one
274       CALL MPI_SENDRECV( ar(nys_l,nxl_l-nbgp_local),   1,                    &
275                          type_x_int(grid_level), psouth, 0,                  &
276                          ar(nyn_l+1,nxl_l-nbgp_local), 1,                    &
277                          type_x_int(grid_level), pnorth, 0,                  &
278                          comm2d, status, ierr )                         
279
280!
281!--    Send rear boundary, receive front one
282       CALL MPI_SENDRECV( ar(nyn_l+1-nbgp_local,nxl_l-nbgp_local), 1,         &
283                          type_x_int(grid_level), pnorth, 1,                  &
284                          ar(nys_l-nbgp_local,nxl_l-nbgp_local),   1,         &
285                          type_x_int(grid_level), psouth, 1,                  &
286                          comm2d, status, ierr )
287
288    ENDIF
289
290#else
291
292!
293!-- Lateral boundary conditions in the non-parallel case
294    IF ( bc_lr_cyc )  THEN
295       ar(:,nxl_l-nbgp_local:nxl_l-1) = ar(:,nxr_l-nbgp_local+1:nxr_l)
296       ar(:,nxr_l+1:nxr_l+nbgp_local) = ar(:,nxl_l:nxl_l+nbgp_local-1)
297    ENDIF
298
299    IF ( bc_ns_cyc )  THEN
300       ar(nys_l-nbgp_local:nys_l-1,:) = ar(nyn_l+1-nbgp_local:nyn_l,:)
301       ar(nyn_l+1:nyn_l+nbgp_local,:) = ar(nys_l:nys_l-1+nbgp_local,:)
302    ENDIF
303
304#endif
305!
306!-- Neumann-conditions at inflow/outflow/nested boundaries
307    IF ( nest_bound_l )  THEN
308       DO  i = nbgp_local, 1, -1
309         ar(:,nxl_l-i) = ar(:,nxl_l)
310       ENDDO
311    ENDIF
312    IF ( nest_bound_r )  THEN
313       DO  i = 1, nbgp_local
314          ar(:,nxr_l+i) = ar(:,nxr_l)
315       ENDDO
316    ENDIF
317    IF ( nest_bound_s )  THEN
318       DO  i = nbgp_local, 1, -1
319         ar(nys_l-i,:) = ar(nys_l,:)
320       ENDDO
321    ENDIF
322    IF ( nest_bound_n )  THEN
323       DO  i = 1, nbgp_local
324         ar(nyn_l+i,:) = ar(nyn_l,:)
325       ENDDO
326    ENDIF
327
328    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
329
330 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.