/[MITgcm]/MITgcm/pkg/exch2/exch2_xyz_rx.template
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/exch2_xyz_rx.template

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (hide annotations) (download)
Mon Apr 5 15:27:06 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint53f_post, checkpoint54a_pre, checkpoint55c_post, checkpoint53b_pre, checkpoint57g_pre, checkpoint57f_post, checkpoint57j_post, checkpoint57b_post, checkpoint53c_post, checkpoint53d_post, checkpoint57f_pre, checkpoint55d_pre, checkpoint57g_post, checkpoint57a_post, checkpoint55j_post, checkpoint56b_post, checkpoint57h_pre, checkpoint54a_post, checkpoint55h_post, checkpoint52n_post, checkpoint54b_post, checkpoint57e_post, checkpoint54d_post, checkpoint56c_post, checkpoint54e_post, checkpoint55b_post, checkpoint57h_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint55a_post, checkpoint57c_pre, checkpoint53b_post, checkpoint55g_post, checkpoint57k_post, checkpoint57d_post, checkpoint55f_post, checkpoint57i_post, checkpoint57a_pre, checkpoint54, checkpoint57, checkpoint56, checkpoint53, checkpoint57h_done, checkpoint53g_post, checkpoint54f_post, eckpoint57e_pre, checkpoint57c_post, checkpoint53d_pre, checkpoint55e_post, checkpoint54c_post, checkpoint55i_post, checkpoint57l_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.1: +7 -1 lines
 o fix "make clean"
 o add CVS Header: and Name:

1 edhill 1.2 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_xyz_rx.template,v 1.1 2004/01/09 20:46:10 afe Exp $
2 afe 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     CBOP
6    
7     C !ROUTINE: EXCH_XYZ_RX
8    
9     C !INTERFACE:
10     SUBROUTINE EXCH2_XYZ_RX(
11     U phi,
12     I myThid )
13     IMPLICIT NONE
14    
15     C !DESCRIPTION:
16     C *==========================================================*
17     C | SUBROUTINE EXCH_XYZ_RX
18     C | o Handle exchanges for _RX, three-dim scalar arrays.
19     C *==========================================================*
20     C | Invoke appropriate exchange routine depending on type
21     C | of grid (cube or globally indexed) to be operated on.
22     C *==========================================================*
23    
24     C !USES:
25     C === Global data ===
26     #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "EESUPPORT.h"
29     #include "W2_EXCH2_TOPOLOGY.h"
30     #include "W2_EXCH2_PARAMS.h"
31    
32     C !INPUT/OUTPUT PARAMETERS:
33     C === Routine arguments ===
34     C phi :: Array with overlap regions are to be exchanged
35     C myThid :: My thread id.
36     _RX phi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:Nr,nSx,nSy)
37     INTEGER myThid
38    
39     C !LOCAL VARIABLES:
40     C == Local variables ==
41     C OL[wens] :: Overlap extents in west, east, north, south.
42     C exchWidth[XY] :: Extent of regions that will be exchanged.
43     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY, myNz
44     INTEGER bi, bj, myTile, i, j, k
45    
46     CEOP
47    
48     OLw = OLx
49     OLe = OLx
50     OLn = OLy
51     OLs = OLy
52     exchWidthX = OLx
53     exchWidthY = OLy
54     myNz = Nr
55     C ** NOTE ** The exchange routine we use here does not
56     C require the preceeding and following barriers.
57     C However, the slow, simple exchange interface
58     C that is calling it here is meant to ensure
59     C that threads are synchronised before exchanges
60     C begine.
61     IF (useCubedSphereExchange) THEN
62     CALL EXCH2_RX1_CUBE( phi, 'T ',
63     I OLw, OLe, OLs, OLn, myNz,
64     I exchWidthX, exchWidthY,
65     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
66    
67     DO bj=myByLo(myThid),myByHi(myThid)
68     DO bi=myBxLo(myThid),myBxHi(myThid)
69     myTile = W2_myTileList(bi)
70     C South-east corner
71     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
72     & exch2_isSedge(myTile) .EQ. 1 ) THEN
73     DO j=1-OLy,0
74     DO i=sNx+1,sNx+OLx
75     DO k=1,Nr
76     phi(i,j,k,bi,bj)=0.
77     ENDDO
78     ENDDO
79     ENDDO
80     ENDIF
81     C North-east corner
82     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
83     & exch2_isNedge(myTile) .EQ. 1 ) THEN
84     DO j=sNy+1,sNy+OLy
85     DO i=sNx+1,sNx+OLx
86     DO k=1,Nr
87     phi(i,j,k,bi,bj)=0.
88     ENDDO
89     ENDDO
90     ENDDO
91     ENDIF
92     C South-west corner
93     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
94     & exch2_isSedge(myTile) .EQ. 1 ) THEN
95     DO j=1-OLy,0
96     DO i=1-OLx,0
97     DO k=1,Nr
98     phi(i,j,k,bi,bj)=0.
99     ENDDO
100     ENDDO
101     ENDDO
102     ENDIF
103     C North-west corner
104     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
105     & exch2_isNedge(myTile) .EQ. 1 ) THEN
106     DO j=sNy+1,sNy+OLy
107     DO i=1-OLx,0
108     DO k=1,Nr
109     phi(i,j,k,bi,bj)=0.
110     ENDDO
111     ENDDO
112     ENDDO
113     ENDIF
114     ENDDO
115     ENDDO
116     CALL EXCH2_RX1_CUBE( phi, 'T ',
117     I OLw, OLe, OLs, OLn, myNz,
118     I exchWidthX, exchWidthY,
119     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
120    
121     DO bj=myByLo(myThid),myByHi(myThid)
122     DO bi=myBxLo(myThid),myBxHi(myThid)
123     myTile = W2_myTileList(bi)
124     C South-east corner
125     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
126     & exch2_isSedge(myTile) .EQ. 1 ) THEN
127     DO j=1-OLy,0
128     DO i=sNx+1,sNx+OLx
129     DO k=1,Nr
130     phi(i,j,k,bi,bj)=0.
131     ENDDO
132     ENDDO
133     ENDDO
134     ENDIF
135     C North-east corner
136     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
137     & exch2_isNedge(myTile) .EQ. 1 ) THEN
138     DO j=sNy+1,sNy+OLy
139     DO i=sNx+1,sNx+OLx
140     DO k=1,Nr
141     phi(i,j,k,bi,bj)=0.
142     ENDDO
143     ENDDO
144     ENDDO
145     ENDIF
146     C South-west corner
147     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
148     & exch2_isSedge(myTile) .EQ. 1 ) THEN
149     DO j=1-OLy,0
150     DO i=1-OLx,0
151     DO k=1,Nr
152     phi(i,j,k,bi,bj)=0.
153     ENDDO
154     ENDDO
155     ENDDO
156     ENDIF
157     C North-west corner
158     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
159     & exch2_isNedge(myTile) .EQ. 1 ) THEN
160     DO j=sNy+1,sNy+OLy
161     DO i=1-OLx,0
162     DO k=1,Nr
163     phi(i,j,k,bi,bj)=0.
164     ENDDO
165     ENDDO
166     ENDDO
167     ENDIF
168     ENDDO
169     ENDDO
170     ELSE
171     CALL EXCH_RX( phi,
172     I OLw, OLe, OLs, OLn, myNz,
173     I exchWidthX, exchWidthY,
174     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
175     ENDIF
176    
177     RETURN
178     END
179 edhill 1.2
180     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
181    
182     CEH3 ;;; Local Variables: ***
183     CEH3 ;;; mode:fortran ***
184     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22