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

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

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

revision 1.1 by jmc, Fri Aug 1 00:45:16 2008 UTC revision 1.2 by jmc, Sat May 30 21:22:13 2009 UTC
# Line 6  C     !ROUTINE: EXCH2_GET_UV_BOUNDS Line 6  C     !ROUTINE: EXCH2_GET_UV_BOUNDS
6    
7  C     !INTERFACE:  C     !INTERFACE:
8        SUBROUTINE EXCH2_GET_UV_BOUNDS(        SUBROUTINE EXCH2_GET_UV_BOUNDS(
9       I           fCode, eWdth,       I                 fCode, eWdth,
10       I           fWedge, fEedge, fSedge, fNedge,       I                 tgTile, tgNb,
11       U           tIlo1, tIhi1, tJlo1, tJhi1,       O                 tIlo1, tIhi1, tJlo1, tJhi1,
12       O           tIlo2, tIhi2, tJlo2, tJhi2,       O                 tIlo2, tIhi2, tJlo2, tJhi2,
13       O           tiStride, tjStride,       O                 tiStride, tjStride,
14       I           e2_pij,       O                 e2_oi1, e2_oj1, e2_oi2, e2_oj2,
15       U           e2_oi1, e2_oj1,       I                 myThid )
      O           e2_oi2, e2_oj2,  
      I           myThid )  
16    
17  C     !DESCRIPTION:  C     !DESCRIPTION:
18    C     Return the index range & step of the part of the array (overlap-region)
19    C     which is going to be updated by the exchange with 1 neighbour.
20    C     2 components vector field (UV) version.
21    
22    
23  C     !USES:  C     !USES:
24        IMPLICIT NONE        IMPLICIT NONE
25  C     == Global data ==  C     == Global data ==
26    #include "SIZE.h"
27    #include "W2_EXCH2_SIZE.h"
28    #include "W2_EXCH2_TOPOLOGY.h"
29    
30  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
31    C     fCode         :: field code (position on staggered grid)
32    C     eWdth         :: width of data region to exchange
33    C     updateCorners :: flag, do update corner halo region if true
34    C     tgTile        :: target tile
35    C     tgNb          :: target Neighbour entry
36    C     tIlo1, tIhi1  :: index range in I that will be filled in 1rst comp. array
37    C     tJlo1, tJhi1  :: index range in J that will be filled in 1rst comp. array
38    C     tIlo2, tIhi2  :: index range in I that will be filled in 2nd  comp. array
39    C     tJlo2, tJhi2  :: index range in J that will be filled in 2nd  comp. array
40    C     tiStride      :: index step  in I that will be filled in target arrays
41    C     tjStride      :: index step  in J that will be filled in target arrays
42    C     e2_oi1        :: index offset in target to source-1 index relation
43    C     e2_oj1        :: index offset in target to source-1 index relation
44    C     e2_oi2        :: index offset in target to source-2 index relation
45    C     e2_oj2        :: index offset in target to source-2 index relation
46    C     myThid        :: my Thread Id. number
47    
48        CHARACTER*2 fCode        CHARACTER*2 fCode
49        INTEGER     eWdth        INTEGER     eWdth
50        INTEGER     fWedge, fEedge, fSedge, fNedge  c     LOGICAL     updateCorners
51          INTEGER     tgTile, tgNb
52        INTEGER     tIlo1, tIhi1, tJlo1, tJhi1        INTEGER     tIlo1, tIhi1, tJlo1, tJhi1
53        INTEGER     tIlo2, tIhi2, tJlo2, tJhi2        INTEGER     tIlo2, tIhi2, tJlo2, tJhi2
54        INTEGER     tiStride, tjStride        INTEGER     tiStride, tjStride
       INTEGER     e2_pij(4)  
55        INTEGER     e2_oi1, e2_oj1        INTEGER     e2_oi1, e2_oj1
56        INTEGER     e2_oi2, e2_oj2        INTEGER     e2_oi2, e2_oj2
57        INTEGER     myThid        INTEGER     myThid
58  C  C
59  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
60        INTEGER     tIlo,  tIhi,  tJlo,  tJhi  C     soTile        :: source tile
61    C     soNb          :: source Neighbour entry
62          INTEGER  soTile
63          INTEGER  soNb
64          INTEGER  tIlo,  tIhi,  tJlo,  tJhi
65          INTEGER  i, e2_pij(4)
66    
67  C---  exch2 target to source index relation:  C---  exch2 target to source index relation:
68  C     is = pij(1)*it + pij(2)*jt + oi  C     is = pij(1)*it + pij(2)*jt + oi
69  C     js = pij(3)*it + pij(4)*jt + oj  C     js = pij(3)*it + pij(4)*jt + oj
70    
71  C---  Save input in local variable  C---  Initialise index range from Topology values:
72        tIlo  = tIlo1        tIlo = exch2_iLo(tgNb,tgTile)
73        tIhi  = tIhi1        tIhi = exch2_iHi(tgNb,tgTile)
74        tJlo  = tJlo1        tJlo = exch2_jLo(tgNb,tgTile)
75        tJhi  = tJhi1        tJhi = exch2_jHi(tgNb,tgTile)
76          soNb = exch2_opposingSend(tgNb,tgTile)
77          soTile = exch2_neighbourId(tgNb,tgTile)
78          e2_oi1 = exch2_oi(soNb,soTile)
79          e2_oj1 = exch2_oj(soNb,soTile)
80          DO i=1,4
81            e2_pij(i) = exch2_pij(i,soNb,soTile)
82          ENDDO
83    
84  C---  Expand index range according to exchange-Width "eWdth"  C---  Expand index range according to exchange-Width "eWdth"
85        IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN        IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN
86  C      Sending to a west edge  C      Filling a west edge overlap
87         tIlo1 = 1-eWdth         tIlo1 = 1-eWdth
88         tIhi1 = 0         tIhi1 = 0
89         tiStride=1         tiStride = 1
90         IF ( tJlo.LE.tJhi ) THEN         IF ( tJlo.LE.tJhi ) THEN
         tJlo1 = tJlo-eWdth+1  
         tJhi1 = tJhi+eWdth-1  
91          tjStride=1          tjStride=1
92         ELSE         ELSE
         tJlo1 = tJlo+eWdth-1  
         tJhi1 = tJhi-eWdth+1  
93          tjStride=-1          tjStride=-1
94         ENDIF         ENDIF
95            tJlo1 = tJlo-tjStride*(eWdth-1)
96            tJhi1 = tJhi+tjStride*(eWdth-1)
97        ENDIF        ENDIF
98        IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN        IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN
99  C      Sending to an east edge  C      Filling an east edge overlap
100           tIlo1 = tIlo
101         tIhi1 = tIhi+eWdth-1         tIhi1 = tIhi+eWdth-1
102         tiStride=1         tiStride = 1
103         IF ( tJlo.LE.tJhi ) THEN         IF ( tJlo.LE.tJhi ) THEN
104          tJlo1 = tJlo-eWdth+1          tjStride = 1
         tJhi1 = tJhi+eWdth-1  
         tjStride=1  
105         ELSE         ELSE
106          tJlo1 = tJlo+eWdth-1          tjStride =-1
         tJhi1 = tJhi-eWdth+1  
         tjStride=-1  
107         ENDIF         ENDIF
108            tJlo1 = tJlo-tjStride*(eWdth-1)
109            tJhi1 = tJhi+tjStride*(eWdth-1)
110        ENDIF        ENDIF
111        IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN        IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN
112  C      Sending to a south edge  C      Filling a south edge overlap
113         tJlo1 = 1-eWdth         tJlo1 = 1-eWdth
114         tJhi1 = 0         tJhi1 = 0
115         tjStride=1         tjStride = 1
116         IF ( tIlo .LE. tIhi ) THEN         IF ( tIlo .LE. tIhi ) THEN
117          tIlo1 = tIlo-eWdth+1          tiStride = 1
         tIhi1 = tIhi+eWdth-1  
         tiStride=1  
118         ELSE         ELSE
119          tIlo1 = tIlo+eWdth-1          tiStride =-1
         tIhi1 = tIhi-eWdth+1  
         tiStride=-1  
120         ENDIF         ENDIF
121            tIlo1 = tIlo-tiStride*(eWdth-1)
122            tIhi1 = tIhi+tiStride*(eWdth-1)
123        ENDIF        ENDIF
124        IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN        IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN
125  C      Sending to a north edge  C      Filling a north edge overlap
126           tJlo1 = tJlo
127         tJhi1 = tJhi+eWdth-1         tJhi1 = tJhi+eWdth-1
128         tjStride=1         tjStride = 1
129         IF ( tIlo.LE.tIhi ) THEN         IF ( tIlo.LE.tIhi ) THEN
130          tIlo1 = tIlo-eWdth+1          tiStride = 1
         tIhi1 = tIhi+eWdth-1  
         tiStride=1  
131         ELSE         ELSE
132          tIlo1 = tIlo+eWdth-1          tiStride =-1
         tIhi1 = tIhi-eWdth+1  
         tiStride=-1  
133         ENDIF         ENDIF
134            tIlo1 = tIlo-tiStride*(eWdth-1)
135            tIhi1 = tIhi+tiStride*(eWdth-1)
136        ENDIF        ENDIF
137    
138  C---  copy to 2nd set of indices  C---  copy to 2nd set of indices
# Line 144  C     (avoid "out-of bounds" problems ; Line 171  C     (avoid "out-of bounds" problems ;
171    
172  C---  Avoid updating (some) tile-corner halo region if across faces  C---  Avoid updating (some) tile-corner halo region if across faces
173  c       IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN  c       IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN
174  c         IF ( fSedge.EQ.1 ) THEN  c         IF ( exch2_isSedge(tgTile).EQ.1 ) THEN
175  C-      West edge is touching the face S edge  C-      West edge is touching the face S edge
176  c           tJlo1 = tJlo+1  c           tJlo1 = tJlo+1
177  c           tJlo2 = tJlo+1  c           tJlo2 = tJlo+1
178  c         ENDIF  c         ENDIF
179  c         IF ( fNedge.EQ.1 ) THEN  c         IF ( exch2_isNedge(tgTile).EQ.1 ) THEN
180  C-      West edge is touching the face N edge  C-      West edge is touching the face N edge
181  c           tJhi1 = tJhi-1  c           tJhi1 = tJhi-1
182  c           tJhi2 = tJhi  c           tJhi2 = tJhi
183  c         ENDIF  c         ENDIF
184  c       ENDIF  c       ENDIF
185          IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN          IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN
186            IF ( fSedge.EQ.1 ) THEN            IF ( exch2_isSedge(tgTile).EQ.1 ) THEN
187  C-      East edge is touching the face S edge  C-      East edge is touching the face S edge
188              tJlo1 = tJlo+1              tJlo1 = tJlo+1
189              tJlo2 = tJlo+1              tJlo2 = tJlo+1
190            ENDIF            ENDIF
191            IF ( fNedge.EQ.1 ) THEN            IF ( exch2_isNedge(tgTile).EQ.1 ) THEN
192  C-      East edge is touching the face N edge  C-      East edge is touching the face N edge
193              tJhi1 = tJhi-1              tJhi1 = tJhi-1
194              tJhi2 = tJhi              tJhi2 = tJhi
195            ENDIF            ENDIF
196          ENDIF          ENDIF
197  c       IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN  c       IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN
198  c         IF ( fWedge.EQ.1 ) THEN  c         IF ( exch2_isWedge(tgTile).EQ.1 ) THEN
199  C-      South edge is touching the face W edge  C-      South edge is touching the face W edge
200  c           tIlo1 = tIlo+1  c           tIlo1 = tIlo+1
201  c           tIlo2 = tIlo+1  c           tIlo2 = tIlo+1
202  c         ENDIF  c         ENDIF
203  c         IF ( fEedge.EQ.1 ) THEN  c         IF ( exch2_isEedge(tgTile).EQ.1 ) THEN
204  C-      South Edge is touching the face E edge  C-      South Edge is touching the face E edge
205  c           tIhi1 = tIhi  c           tIhi1 = tIhi
206  c           tIhi2 = tIhi-1  c           tIhi2 = tIhi-1
207  c         ENDIF  c         ENDIF
208  c       ENDIF  c       ENDIF
209          IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN          IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN
210            IF ( fWedge.EQ.1 ) THEN            IF ( exch2_isWedge(tgTile).EQ.1 ) THEN
211  C-      North edge is touching the face W edge  C-      North edge is touching the face W edge
212              tIlo1 = tIlo+1              tIlo1 = tIlo+1
213              tIlo2 = tIlo+1              tIlo2 = tIlo+1
214            ENDIF            ENDIF
215            IF ( fEedge.EQ.1 ) THEN            IF ( exch2_isEedge(tgTile).EQ.1 ) THEN
216  C-      North Edge is touching the face E edge  C-      North Edge is touching the face E edge
217              tIhi1 = tIhi              tIhi1 = tIhi
218              tIhi2 = tIhi-1              tIhi2 = tIhi-1

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22