source: palm/tags/release-3.1c/SOURCE/exchange_horiz.f90 @ 112

Last change on this file since 112 was 4, checked in by raasch, 17 years ago

Id keyword set as property for all *.f90 files

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