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

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

last commit documented

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