/[MITgcm]/MITgcm/eesupp/src/fill_cs_corner_uv_rl.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/fill_cs_corner_uv_rl.F

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


Revision 1.1 - (show annotations) (download)
Wed Dec 3 17:22:22 2014 UTC (9 years, 4 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, HEAD
add a _RL version of fill_cs_corner_uv_rs.F

1 C $Header: $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_EEOPTIONS.h"
6
7 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 CBOP
9 C !ROUTINE: FILL_CS_CORNER_UV_RL
10
11 C !INTERFACE:
12 SUBROUTINE FILL_CS_CORNER_UV_RL(
13 I withSigns,
14 U uFld, vFld,
15 I bi,bj, myThid)
16 IMPLICIT NONE
17
18 C !DESCRIPTION:
19 C *==========================================================*
20 C | SUBROUTINE FILL_CS_CORNER_UV_RL
21 C | o Fill the corner-halo region of CS-grid,
22 C | for a 2 components, C-grid vector field
23 C *==========================================================*
24 C | o the corner halo region is filled with valid values
25 C | in order to extend in X and Y direction calculations
26 C | of fluxes, on a wide stencil.
27 C *==========================================================*
28 C | o this routine is a copy of S/R FILL_CS_CORNER_UV_RS
29 C *==========================================================*
30
31 C !USES:
32 C == Global variables ==
33
34 #include "SIZE.h"
35 #include "EEPARAMS.h"
36 #ifdef ALLOW_EXCH2
37 #include "W2_EXCH2_SIZE.h"
38 #include "W2_EXCH2_TOPOLOGY.h"
39 #endif /* ALLOW_EXCH2 */
40
41 C !INPUT/OUTPUT PARAMETERS:
42 C == Routine arguments ==
43 C
44 C withSigns :: uFld,vFld are vector components
45 C uFld :: u-component, at C-grid West point location
46 C vFld :: v-component, at C-grid SOuth point location
47 C bi,bj :: tile indices
48 C myThid :: thread number
49 LOGICAL withSigns
50 _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 INTEGER bi,bj
53 INTEGER myThid
54
55 C !LOCAL VARIABLES:
56 C == Local variables ==
57 C i,j :: loop indices
58 C myTile :: tile number
59 INTEGER i,j
60 LOGICAL southWestCorner
61 LOGICAL southEastCorner
62 LOGICAL northWestCorner
63 LOGICAL northEastCorner
64 _RL negOne
65 #ifdef ALLOW_EXCH2
66 INTEGER myTile
67 #endif
68 CEOP
69
70 IF (useCubedSphereExchange) THEN
71
72 negOne = 1. _d 0
73 IF (withSigns) negOne = -1. _d 0
74
75 #ifdef ALLOW_EXCH2
76 myTile = W2_myTileList(bi,bj)
77 southWestCorner = exch2_isWedge(myTile).EQ.1
78 & .AND. exch2_isSedge(myTile).EQ.1
79 southEastCorner = exch2_isEedge(myTile).EQ.1
80 & .AND. exch2_isSedge(myTile).EQ.1
81 northEastCorner = exch2_isEedge(myTile).EQ.1
82 & .AND. exch2_isNedge(myTile).EQ.1
83 northWestCorner = exch2_isWedge(myTile).EQ.1
84 & .AND. exch2_isNedge(myTile).EQ.1
85 #else
86 southWestCorner = .TRUE.
87 southEastCorner = .TRUE.
88 northWestCorner = .TRUE.
89 northEastCorner = .TRUE.
90 #endif
91
92 C-- To extend calculations in X direction, fill uFld array
93 C with valid value in the corner.
94 C e.g., NW corner: copy V( 0,sNy ) into U( -1,sNy+1)
95 C copy V( 0,sNy-1) into U( -2,sNy+1)
96 C copy V( -1,sNy ) into U( -1,sNy+2)
97 C copy V( -1,sNy-1) into U( -2,sNy+2)
98 C | |
99 C U(-1,sNy+1) U(1,sNy+1) U(2,sNy+1)
100 C | ^ | |
101 C -----|--\--------corner----------|
102 C | \ | |
103 C | \ |
104 C | \ |
105 C -----|---V(0,sNy)--|---------------
106 C | |
107 C
108 C-- to extend calculations in Y direction, fill vFld array
109 C with valid value in the corner.
110 C e.g., NW corner: copy U( 2,sNy+1) into V( 0,sNy+2)
111 C copy U( 3,sNy+1) into V( 0,sNy+3)
112 C copy U( 2,sNy+2) into V( -1,sNy+2)
113 C copy U( 3,sNy+2) into V( -1,sNy+3)
114 C | | |
115 C -----|--V(0,sNy+2)--|--------------|
116 C | ^====================\
117 C U(-1,sNy+1) U(1,sNy+1) U(2,sNy+1)
118 C | | |
119 C -----|--V(0,sNy+1)--o--------------|
120 C | |\ |
121 C | | \=corner
122 C | |
123 C -----|--V(0,sNy)----|--
124 C | |
125 C
126
127 IF ( southWestCorner ) THEN
128 C- prepare for direction X:
129 DO j=1,OLy
130 DO i=1,OLx
131 uFld( 1-i , 1-j ) = negOne*vFld( 1-j , 1+i )
132 ENDDO
133 ENDDO
134 C- prepare for direction Y:
135 DO j=1,OLy
136 DO i=1,OLx
137 vFld( 1-i , 1-j ) = negOne*uFld( 1+j , 1-i )
138 ENDDO
139 ENDDO
140 ENDIF
141
142 IF ( southEastCorner ) THEN
143 C- prepare for direction X:
144 DO j=1,OLy
145 DO i=2,OLx
146 uFld(sNx+i, 1-j ) = vFld(sNx+j, i )
147 ENDDO
148 ENDDO
149 C- prepare for direction Y:
150 DO j=1,OLy
151 DO i=1,OLx
152 vFld(sNx+i, 1-j ) = uFld(sNx+1-j, 1-i )
153 ENDDO
154 ENDDO
155 ENDIF
156
157 IF ( northWestCorner ) THEN
158 C- prepare for direction X:
159 DO j=1,OLy
160 DO i=1,OLx
161 uFld( 1-i ,sNy+j) = vFld( 1-j , sNy+1-i )
162 ENDDO
163 ENDDO
164 C- prepare for direction Y:
165 DO j=2,OLy
166 DO i=1,OLx
167 vFld( 1-i ,sNy+j) = uFld( j , sNy+i )
168 ENDDO
169 ENDDO
170 ENDIF
171
172 IF ( northEastCorner ) THEN
173 C- prepare for direction X:
174 DO j=1,OLy
175 DO i=2,OLx
176 uFld(sNx+i,sNy+j) = negOne*vFld(sNx+j, sNy+2-i )
177 ENDDO
178 ENDDO
179 C- prepare for direction Y:
180 DO j=2,OLy
181 DO i=1,OLx
182 vFld(sNx+i,sNy+j) = negOne*uFld(sNx+2-j, sNy+i )
183 ENDDO
184 ENDDO
185 ENDIF
186
187 C-- End useCubedSphereExchange
188 ENDIF
189
190 RETURN
191 END

  ViewVC Help
Powered by ViewVC 1.1.22