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

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

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


Revision 1.4 - (hide annotations) (download)
Tue May 12 19:44:58 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61o, checkpoint61r, checkpoint61p, checkpoint61q
Changes since 1.3: +4 -1 lines
new header files "W2_EXCH2_SIZE.h" (taken out of W2_EXCH2_TOPOLOGY.h)
             and "W2_EXCH2_BUFFER.h" (taken out of W2_EXCH2_PARAMS.h)

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

  ViewVC Help
Powered by ViewVC 1.1.22