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

Last change on this file since 1834 was 1818, checked in by maronga, 8 years ago

last commit documented / copyright update

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