source: palm/trunk/SOURCE/exchange_horiz.f90 @ 76

Last change on this file since 76 was 75, checked in by raasch, 17 years ago

preliminary update for changes concerning non-cyclic boundary conditions

  • Property svn:keywords set to Id
File size: 3.8 KB
Line 
1 SUBROUTINE exchange_horiz( ar )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Special cases for additional gridpoints along x or y in case of non-cyclic
7! boundary conditions are not regarded any more
8!
9! Former revisions:
10! -----------------
11! $Id: exchange_horiz.f90 75 2007-03-22 09:54:05Z raasch $
12! RCS Log replace by Id keyword, revision history cleaned up
13!
14! Revision 1.16  2006/02/23 12:19:08  raasch
15! anz_yz renamed ngp_yz
16!
17! Revision 1.1  1997/07/24 11:13:29  raasch
18! Initial revision
19!
20!
21! Description:
22! ------------
23! Exchange of lateral boundary values (parallel computers) and cyclic
24! lateral boundary conditions, respectively.
25!------------------------------------------------------------------------------!
26
27    USE control_parameters
28    USE cpulog
29    USE indices
30    USE interfaces
31    USE pegrid
32
33    IMPLICIT NONE
34
35#if defined( __parallel )
36    INTEGER, DIMENSION(4)                 ::  req
37    INTEGER, DIMENSION(MPI_STATUS_SIZE,4) ::  wait_stat
38#endif
39
40    REAL ::  ar(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
41
42
43    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'start' )
44
45#if defined( __parallel )
46
47!
48!-- Exchange of lateral boundary values for parallel computers
49    IF ( pdims(1) == 1  .OR.  mg_switch_to_pe0 )  THEN
50!
51!--    One-dimensional decomposition along y, boundary values can be exchanged
52!--    within the PE memory
53       IF ( bc_lr == 'cyclic' )  THEN
54          ar(:,nys:nyn,nxl-1) = ar(:,nys:nyn,nxr)
55          ar(:,nys:nyn,nxr+1) = ar(:,nys:nyn,nxl)
56       ENDIF
57
58    ELSE
59
60       req = 0
61!
62!--    Send left boundary, receive right one
63       CALL MPI_ISEND(                                                     &
64               ar(nzb,nys-1,nxl), ngp_yz(grid_level), MPI_REAL, pleft,  0, &
65                          comm2d, req(1), ierr )
66       CALL MPI_IRECV(                                                       &
67               ar(nzb,nys-1,nxr+1), ngp_yz(grid_level), MPI_REAL, pright, 0, &
68                          comm2d, req(2), ierr )
69!
70!--    Send right boundary, receive left one
71       CALL MPI_ISEND(                                                     &
72               ar(nzb,nys-1,nxr), ngp_yz(grid_level), MPI_REAL, pright, 1, &
73                          comm2d, req(3), ierr )
74       CALL MPI_IRECV(                                                       &
75               ar(nzb,nys-1,nxl-1), ngp_yz(grid_level), MPI_REAL, pleft,  1, &
76                          comm2d, req(4), ierr )
77       CALL MPI_WAITALL( 4, req, wait_stat, ierr )
78
79    ENDIF
80
81
82    IF ( pdims(2) == 1  .OR.  mg_switch_to_pe0 )  THEN
83!
84!--    One-dimensional decomposition along x, boundary values can be exchanged
85!--    within the PE memory
86       IF ( bc_ns == 'cyclic' )  THEN
87          ar(:,nys-1,:) = ar(:,nyn,:)
88          ar(:,nyn+1,:) = ar(:,nys,:)
89       ENDIF
90
91    ELSE
92
93       req = 0
94!
95!--    Send front boundary, receive rear one
96       CALL MPI_ISEND( ar(nzb,nys,nxl-1),   1, type_xz(grid_level), psouth, 0, &
97                       comm2d, req(1), ierr )
98       CALL MPI_IRECV( ar(nzb,nyn+1,nxl-1), 1, type_xz(grid_level), pnorth, 0, &
99                       comm2d, req(2), ierr )
100!
101!--    Send rear boundary, receive front one
102       CALL MPI_ISEND( ar(nzb,nyn,nxl-1),   1, type_xz(grid_level), pnorth, 1, &
103                       comm2d, req(3), ierr )
104       CALL MPI_IRECV( ar(nzb,nys-1,nxl-1), 1, type_xz(grid_level), psouth, 1, &
105                       comm2d, req(4), ierr )
106       call MPI_WAITALL( 4, req, wait_stat, ierr )
107
108    ENDIF
109
110
111#else
112
113!
114!-- Lateral boundary conditions in the non-parallel case
115    IF ( bc_lr == 'cyclic' )  THEN
116       ar(:,nys:nyn,nxl-1) = ar(:,nys:nyn,nxr)
117       ar(:,nys:nyn,nxr+1) = ar(:,nys:nyn,nxl)
118    ENDIF
119
120    IF ( bc_ns == 'cyclic' )  THEN
121       ar(:,nys-1,:) = ar(:,nyn,:)
122       ar(:,nyn+1,:) = ar(:,nys,:)
123    ENDIF
124
125#endif
126
127    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'stop' )
128
129 END SUBROUTINE exchange_horiz
Note: See TracBrowser for help on using the repository browser.