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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

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