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

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

Initial repository layout and content

File size: 5.6 KB
Line 
1 SUBROUTINE exchange_horiz( ar, xrp, ynp )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: exchange_horiz.f90,v $
11! Revision 1.16  2006/02/23 12:19:08  raasch
12! anz_yz renamed ngp_yz
13!
14! Revision 1.15  2005/03/26 20:20:39  raasch
15! Extensions for non-cyclic boundary conditions along x or y
16!
17! Revision 1.14  2003/10/29 08:51:10  raasch
18! Exchange of boundaries within the PE memory in case that multigrid method
19! has switched to PE0 only
20!
21! Revision 1.13  2003/03/16 09:30:38  raasch
22! Two underscores (_) are placed in front of all define-strings
23!
24! Revision 1.12  2002/12/20 10:40:08  raasch
25! Integer variables will be defined in the parallel case only
26!
27! Revision 1.11  2002/12/19 14:46:43  raasch
28! Cyclic boundary conditions along y used instead of sendrecv in case of
29! pdims(2)=1. SENDRECV replaced by nonblocking routines ISEND and IRECV.
30! Array "feld" is renamed to "ar".
31!
32! Revision 1.9  2002/04/16  08:16:50  08:16:50  raasch (Siegfried Raasch)
33! Cyclic boundary conditions along x used instead of sendrecv in case of
34! pdims(1)=1
35!
36! Revision 1.8  2001/07/20 13:04:59  raasch
37! anz_yz and type_xz changed to arrays to allow for the boundary value exchange
38! for the different grid levels used in the multigrid method,
39! +module control_parameters
40!
41! Revision 1.7  2001/03/30 07:23:00  raasch
42! Translation of remaining German identifiers (variables, subroutines, etc.)
43!
44! Revision 1.6  2001/01/22 06:36:07  raasch
45! Module test_variables removed
46!
47! Revision 1.5  2000/12/20 12:06:44  letzel
48! All comments translated into English.
49!
50! Revision 1.4  1998/07/06 12:13:36  raasch
51! + USE test_variables
52!
53! Revision 1.3  1998/01/23 09:57:45  raasch
54! Umbenennung von anz_yz_p in anz_yz sowie von type_xz_p in type_xz
55!
56! Revision 1.2  1997/08/11 06:14:55  raasch
57! Felder werden jetzt ueber Formalparameter uebergeben.
58!
59! Revision 1.1  1997/07/24 11:13:29  raasch
60! Initial revision
61!
62!
63! Description:
64! ------------
65! Exchange of lateral boundary values (parallel computers) and cyclic
66! lateral boundary conditions, respectively.
67!------------------------------------------------------------------------------!
68
69    USE control_parameters
70    USE cpulog
71    USE indices
72    USE interfaces
73    USE pegrid
74
75    IMPLICIT NONE
76
77    INTEGER ::  xrp, ynp
78
79#if defined( __parallel )
80    INTEGER                               ::  typexz
81    INTEGER, DIMENSION(4)                 ::  req
82    INTEGER, DIMENSION(MPI_STATUS_SIZE,4) ::  wait_stat
83#endif
84
85    REAL ::  ar(nzb:nzt+1,nys-1:nyn+ynp+1,nxl-1:nxr+xrp+1)
86
87
88    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'start' )
89
90#if defined( __parallel )
91
92!
93!-- Exchange of lateral boundary values for parallel computers
94    IF ( pdims(1) == 1  .OR.  mg_switch_to_pe0 )  THEN
95!
96!--    One-dimensional decomposition along y, boundary values can be exchanged
97!--    within the PE memory
98       IF ( bc_lr == 'cyclic' )  THEN
99          ar(:,nys:nyn,nxl-1) = ar(:,nys:nyn,nxr)
100          ar(:,nys:nyn,nxr+1) = ar(:,nys:nyn,nxl)
101       ENDIF
102
103    ELSE
104       req = 0
105!
106!--    Send left boundary, receive right one
107       CALL MPI_ISEND(                                                     &
108               ar(nzb,nys-1,nxl), ngp_yz(grid_level), MPI_REAL, pleft,  0, &
109                          comm2d, req(1), ierr )
110       CALL MPI_IRECV(                                                       &
111               ar(nzb,nys-1,nxr+1), ngp_yz(grid_level), MPI_REAL, pright, 0, &
112                          comm2d, req(2), ierr )
113!
114!--    Send right boundary, receive left one
115       CALL MPI_ISEND(                                                     &
116               ar(nzb,nys-1,nxr), ngp_yz(grid_level), MPI_REAL, pright, 1, &
117                          comm2d, req(3), ierr )
118       CALL MPI_IRECV(                                                       &
119               ar(nzb,nys-1,nxl-1), ngp_yz(grid_level), MPI_REAL, pleft,  1, &
120                          comm2d, req(4), ierr )
121       call MPI_Waitall (4,req,wait_stat,ierr)
122    ENDIF
123
124
125    IF ( pdims(2) == 1  .OR.  mg_switch_to_pe0 )  THEN
126!
127!--    One-dimensional decomposition along x, boundary values can be exchanged
128!--    within the PE memory
129       IF ( bc_ns == 'cyclic' )  THEN
130          ar(:,nys-1,:) = ar(:,nyn,:)
131          ar(:,nyn+1,:) = ar(:,nys,:)
132       ENDIF
133
134    ELSE
135!
136!--    Set the MPI data type, which depends on the size of the array
137!--    (the v array has an additional gridpoint along y in case of non-cyclic
138!--    boundary conditions)
139       IF ( ynp == 0 )  THEN
140          typexz = type_xz(grid_level)
141       ELSE
142          typexz = type_xz_p
143       ENDIF
144
145       req = 0
146!
147!--    Send front boundary, receive rear one
148       CALL MPI_ISEND( ar(nzb,nys,nxl-1),   1, typexz, psouth, 0, comm2d, &
149                       req(1), ierr )
150       CALL MPI_IRECV( ar(nzb,nyn+1,nxl-1), 1, typexz, pnorth, 0, comm2d, &
151                       req(2), ierr )
152!
153!--    Send rear boundary, receive front one
154       CALL MPI_ISEND( ar(nzb,nyn,nxl-1),   1, typexz, pnorth, 1, comm2d, &
155                       req(3), ierr )
156       CALL MPI_IRECV( ar(nzb,nys-1,nxl-1), 1, typexz, psouth, 1, comm2d, &
157                       req(4), ierr )
158       call MPI_Waitall (4,req,wait_stat,ierr)
159    ENDIF
160
161
162#else
163
164!
165!-- Lateral boundary conditions in the non-parallel case
166    IF ( bc_lr == 'cyclic' )  THEN
167       ar(:,nys:nyn,nxl-1) = ar(:,nys:nyn,nxr)
168       ar(:,nys:nyn,nxr+1) = ar(:,nys:nyn,nxl)
169    ENDIF
170
171    IF ( bc_ns == 'cyclic' )  THEN
172       ar(:,nys-1,:) = ar(:,nyn,:)
173       ar(:,nyn+1,:) = ar(:,nys,:)
174    ENDIF
175
176#endif
177
178    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'stop' )
179
180 END SUBROUTINE exchange_horiz
Note: See TracBrowser for help on using the repository browser.