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

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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