/[MITgcm]/MITgcm/pkg/exch2/exch2_get_uv_bounds.F
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/exch2_get_uv_bounds.F

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


Revision 1.1 - (hide annotations) (download)
Fri Aug 1 00:45:16 2008 UTC (15 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
change index bounds in rx2_cube exchanges (new S/R: EXCH2_GET_UV_BOUNDS)
- no longer depend on the order sequence (N,S,E,W).
- 3rd exchange no longer needed (tested with 24 tiles).
- same modif to hand-written adjoint S/R (global_ocean.cs32x15: zero diff)
- exch_UV_A-grid readily available (but not yet tested).

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_get_recv_bounds.F,v 1.4 2008/07/23 21:06:06 jmc Exp $
2     C $Name: $
3    
4     CBOP
5     C !ROUTINE: EXCH2_GET_UV_BOUNDS
6    
7     C !INTERFACE:
8     SUBROUTINE EXCH2_GET_UV_BOUNDS(
9     I fCode, eWdth,
10     I fWedge, fEedge, fSedge, fNedge,
11     U tIlo1, tIhi1, tJlo1, tJhi1,
12     O tIlo2, tIhi2, tJlo2, tJhi2,
13     O tiStride, tjStride,
14     I e2_pij,
15     U e2_oi1, e2_oj1,
16     O e2_oi2, e2_oj2,
17     I myThid )
18    
19     C !DESCRIPTION:
20    
21     C !USES:
22     IMPLICIT NONE
23     C == Global data ==
24    
25     C !INPUT/OUTPUT PARAMETERS:
26    
27     CHARACTER*2 fCode
28     INTEGER eWdth
29     INTEGER fWedge, fEedge, fSedge, fNedge
30     INTEGER tIlo1, tIhi1, tJlo1, tJhi1
31     INTEGER tIlo2, tIhi2, tJlo2, tJhi2
32     INTEGER tiStride, tjStride
33     INTEGER e2_pij(4)
34     INTEGER e2_oi1, e2_oj1
35     INTEGER e2_oi2, e2_oj2
36     INTEGER myThid
37     C
38     C !LOCAL VARIABLES:
39     INTEGER tIlo, tIhi, tJlo, tJhi
40    
41     C--- exch2 target to source index relation:
42     C is = pij(1)*it + pij(2)*jt + oi
43     C js = pij(3)*it + pij(4)*jt + oj
44    
45     C--- Save input in local variable
46     tIlo = tIlo1
47     tIhi = tIhi1
48     tJlo = tJlo1
49     tJhi = tJhi1
50    
51     C--- Expand index range according to exchange-Width "eWdth"
52     IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN
53     C Sending to a west edge
54     tIlo1 = 1-eWdth
55     tIhi1 = 0
56     tiStride=1
57     IF ( tJlo.LE.tJhi ) THEN
58     tJlo1 = tJlo-eWdth+1
59     tJhi1 = tJhi+eWdth-1
60     tjStride=1
61     ELSE
62     tJlo1 = tJlo+eWdth-1
63     tJhi1 = tJhi-eWdth+1
64     tjStride=-1
65     ENDIF
66     ENDIF
67     IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN
68     C Sending to an east edge
69     tIhi1 = tIhi+eWdth-1
70     tiStride=1
71     IF ( tJlo.LE.tJhi ) THEN
72     tJlo1 = tJlo-eWdth+1
73     tJhi1 = tJhi+eWdth-1
74     tjStride=1
75     ELSE
76     tJlo1 = tJlo+eWdth-1
77     tJhi1 = tJhi-eWdth+1
78     tjStride=-1
79     ENDIF
80     ENDIF
81     IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN
82     C Sending to a south edge
83     tJlo1 = 1-eWdth
84     tJhi1 = 0
85     tjStride=1
86     IF ( tIlo .LE. tIhi ) THEN
87     tIlo1 = tIlo-eWdth+1
88     tIhi1 = tIhi+eWdth-1
89     tiStride=1
90     ELSE
91     tIlo1 = tIlo+eWdth-1
92     tIhi1 = tIhi-eWdth+1
93     tiStride=-1
94     ENDIF
95     ENDIF
96     IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN
97     C Sending to a north edge
98     tJhi1 = tJhi+eWdth-1
99     tjStride=1
100     IF ( tIlo.LE.tIhi ) THEN
101     tIlo1 = tIlo-eWdth+1
102     tIhi1 = tIhi+eWdth-1
103     tiStride=1
104     ELSE
105     tIlo1 = tIlo+eWdth-1
106     tIhi1 = tIhi-eWdth+1
107     tiStride=-1
108     ENDIF
109     ENDIF
110    
111     C--- copy to 2nd set of indices
112     tIlo2 = tIlo1
113     tIhi2 = tIhi1
114     tJlo2 = tJlo1
115     tJhi2 = tJhi1
116     e2_oi2 = e2_oi1
117     e2_oj2 = e2_oj1
118    
119     IF ( fCode.EQ.'Cg' ) THEN
120     C--- UV C-Grid specific code: start here
121    
122     C--- half grid-cell location with inverse index relation
123     C => increase the offset by 1 (relative to tracer cell-centered offset)
124     C if pij(1) is -1 then +i in source aligns with -i in target
125     C if pij(3) is -1 then +j in source aligns with -i in target
126     IF ( e2_pij(1) .EQ. -1 ) THEN
127     e2_oi1 = e2_oi1 + 1
128     ENDIF
129     IF ( e2_pij(3) .EQ. -1 ) THEN
130     e2_oj1 = e2_oj1 + 1
131     ENDIF
132     C if pij(2) is -1 then +i in source aligns with -j in target
133     C if pij(4) is -1 then +j in source aligns with -j in target
134     IF ( e2_pij(2) .EQ. -1 ) THEN
135     e2_oi2 = e2_oi2 + 1
136     ENDIF
137     IF ( e2_pij(4) .EQ. -1 ) THEN
138     e2_oj2 = e2_oj2 + 1
139     ENDIF
140     C-- as a consequence, need also to increase the index lower bound
141     C (avoid "out-of bounds" problems ; formerly itlreduce,jtlreduce)
142     IF ( e2_pij(1).EQ.-1 .OR. e2_pij(3).EQ.-1 ) tIlo1 = tIlo1+1
143     IF ( e2_pij(2).EQ.-1 .OR. e2_pij(4).EQ.-1 ) tJlo2 = tJlo2+1
144    
145     C--- Avoid updating (some) tile-corner halo region if across faces
146     c IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN
147     c IF ( fSedge.EQ.1 ) THEN
148     C- West edge is touching the face S edge
149     c tJlo1 = tJlo+1
150     c tJlo2 = tJlo+1
151     c ENDIF
152     c IF ( fNedge.EQ.1 ) THEN
153     C- West edge is touching the face N edge
154     c tJhi1 = tJhi-1
155     c tJhi2 = tJhi
156     c ENDIF
157     c ENDIF
158     IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN
159     IF ( fSedge.EQ.1 ) THEN
160     C- East edge is touching the face S edge
161     tJlo1 = tJlo+1
162     tJlo2 = tJlo+1
163     ENDIF
164     IF ( fNedge.EQ.1 ) THEN
165     C- East edge is touching the face N edge
166     tJhi1 = tJhi-1
167     tJhi2 = tJhi
168     ENDIF
169     ENDIF
170     c IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN
171     c IF ( fWedge.EQ.1 ) THEN
172     C- South edge is touching the face W edge
173     c tIlo1 = tIlo+1
174     c tIlo2 = tIlo+1
175     c ENDIF
176     c IF ( fEedge.EQ.1 ) THEN
177     C- South Edge is touching the face E edge
178     c tIhi1 = tIhi
179     c tIhi2 = tIhi-1
180     c ENDIF
181     c ENDIF
182     IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN
183     IF ( fWedge.EQ.1 ) THEN
184     C- North edge is touching the face W edge
185     tIlo1 = tIlo+1
186     tIlo2 = tIlo+1
187     ENDIF
188     IF ( fEedge.EQ.1 ) THEN
189     C- North Edge is touching the face E edge
190     tIhi1 = tIhi
191     tIhi2 = tIhi-1
192     ENDIF
193     ENDIF
194    
195     C--- UV C-Grid specific code: end
196    
197     ELSEIF ( fCode.NE.'Ag' ) THEN
198     STOP 'ABNORMAL END: S/R EXCH2_GET_UV_BOUNDS (wrong fCode)'
199     ENDIF
200    
201     RETURN
202     END

  ViewVC Help
Powered by ViewVC 1.1.22