source: palm/tags/release-5.0/SOURCE/exchange_horiz_2d.f90

Last change on this file was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

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