/[MITgcm]/MITgcm/model/src/ini_spherical_polar_grid.F
ViewVC logotype

Contents of /MITgcm/model/src/ini_spherical_polar_grid.F

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


Revision 1.31 - (show annotations) (download)
Sun Feb 17 02:27:39 2013 UTC (11 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, HEAD
Changes since 1.30: +18 -14 lines
add 1 argument to S/R CALC_GRID_ANGLES

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_spherical_polar_grid.F,v 1.30 2011/12/25 22:24:35 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 #undef USE_BACKWARD_COMPATIBLE_GRID
7
8 CBOP
9 C !ROUTINE: INI_SPHERICAL_POLAR_GRID
10 C !INTERFACE:
11 SUBROUTINE INI_SPHERICAL_POLAR_GRID( myThid )
12
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | SUBROUTINE INI_SPHERICAL_POLAR_GRID
16 C | o Initialise model coordinate system arrays
17 C *==========================================================*
18 C | These arrays are used throughout the code in evaluating
19 C | gradients, integrals and spatial avarages. This routine
20 C | is called separately by each thread and initialise only
21 C | the region of the domain it is "responsible" for.
22 C | Under the spherical polar grid mode primitive distances
23 C | in X and Y are in degrees. Distance in Z are in m or Pa
24 C | depending on the vertical gridding mode.
25 C *==========================================================*
26 C \ev
27
28 C !USES:
29 IMPLICIT NONE
30 C === Global variables ===
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "PARAMS.h"
34 #include "GRID.h"
35
36 C !INPUT/OUTPUT PARAMETERS:
37 C == Routine arguments ==
38 C myThid :: my Thread Id Number
39 INTEGER myThid
40
41 C !LOCAL VARIABLES:
42 C == Local variables ==
43 C bi,bj :: tile indices
44 C i, j :: loop counters
45 C lat :: Temporary variables used to hold latitude values.
46 C dlat :: Temporary variables used to hold latitudes increment.
47 C dlon :: Temporary variables used to hold longitude increment.
48 C delXloc :: mesh spacing in X direction
49 C delYloc :: mesh spacing in Y direction
50 C xGloc :: mesh corner-point location (local "Long" real array type)
51 C yGloc :: mesh corner-point location (local "Long" real array type)
52 LOGICAL skipCalcAngleC
53 INTEGER bi, bj
54 INTEGER i, j
55 INTEGER gridNx, gridNy
56 _RL lat, dlat, dlon
57 C NOTICE the extended range of indices!!
58 _RL delXloc(0-OLx:sNx+OLx)
59 _RL delYloc(0-OLy:sNy+OLy)
60 C NOTICE the extended range of indices!!
61 _RL xGloc(1-OLx:sNx+OLx+1,1-OLy:sNy+OLy+1)
62 _RL yGloc(1-OLx:sNx+OLx+1,1-OLy:sNy+OLy+1)
63 CEOP
64
65 C-- For each tile ...
66 DO bj = myByLo(myThid), myByHi(myThid)
67 DO bi = myBxLo(myThid), myBxHi(myThid)
68
69 C-- set tile local mesh (same units as delX,deY)
70 C corresponding to coordinates of cell corners for N+1 grid-lines
71 CALL INI_LOCAL_GRID(
72 O xGloc, yGloc,
73 O delXloc, delYloc,
74 O gridNx, gridNy,
75 I bi, bj, myThid )
76
77 C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
78 DO j=1-OLy,sNy+OLy
79 DO i=1-OLx,sNx+OLx
80 xG(i,j,bi,bj) = xGloc(i,j)
81 yG(i,j,bi,bj) = yGloc(i,j)
82 ENDDO
83 ENDDO
84
85 C-- Calculate [xC,yC], coordinates of cell centers
86 DO j=1-OLy,sNy+OLy
87 DO i=1-OLx,sNx+OLx
88 C by averaging
89 xC(i,j,bi,bj) = 0.25 _d 0*(
90 & xGloc(i,j)+xGloc(i+1,j)+xGloc(i,j+1)+xGloc(i+1,j+1) )
91 yC(i,j,bi,bj) = 0.25 _d 0*(
92 & yGloc(i,j)+yGloc(i+1,j)+yGloc(i,j+1)+yGloc(i+1,j+1) )
93 ENDDO
94 ENDDO
95
96 C-- Calculate [dxF,dyF], lengths between cell faces (through center)
97 DO j=1-OLy,sNy+OLy
98 DO i=1-OLx,sNx+OLx
99 C by averaging
100 c dxF(i,j,bi,bj) = 0.5*(dxG(i,j,bi,bj)+dxG(i,j+1,bi,bj))
101 c dyF(i,j,bi,bj) = 0.5*(dyG(i,j,bi,bj)+dyG(i+1,j,bi,bj))
102 C by formula
103 lat = yC(i,j,bi,bj)
104 dlon = delXloc(i)
105 dlat = delYloc(j)
106 dxF(i,j,bi,bj) = rSphere*COS(lat*deg2rad)*dlon*deg2rad
107 dyF(i,j,bi,bj) = rSphere*dlat*deg2rad
108 ENDDO
109 ENDDO
110
111 C-- Calculate [dxG,dyG], lengths along cell boundaries
112 DO j=1-OLy,sNy+OLy
113 DO i=1-OLx,sNx+OLx
114 C by averaging
115 c dxG(i,j,bi,bj) = 0.5*(dxF(i,j,bi,bj)+dxF(i,j-1,bi,bj))
116 c dyG(i,j,bi,bj) = 0.5*(dyF(i,j,bi,bj)+dyF(i-1,j,bi,bj))
117 C by formula
118 lat = 0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
119 dlon = delXloc(i)
120 dlat = delYloc(j)
121 dxG(i,j,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
122 IF (dxG(i,j,bi,bj).LT.1.) dxG(i,j,bi,bj)=0.
123 dyG(i,j,bi,bj) = rSphere*dlat*deg2rad
124 ENDDO
125 ENDDO
126
127 C-- The following arrays are not defined in some parts of the halo
128 C region. We set them to zero here for safety. If they are ever
129 C referred to, especially in the denominator then it is a mistake!
130 C Note: this is now done earlier in main S/R INI_GRID
131 c DO j=1-OLy,sNy+OLy
132 c DO i=1-OLx,sNx+OLx
133 c dxC(i,j,bi,bj) = 0.
134 c dyC(i,j,bi,bj) = 0.
135 c dxV(i,j,bi,bj) = 0.
136 c dyU(i,j,bi,bj) = 0.
137 c rAw(i,j,bi,bj) = 0.
138 c rAs(i,j,bi,bj) = 0.
139 c ENDDO
140 c ENDDO
141
142 C-- Calculate [dxC], zonal length between cell centers
143 DO j=1-OLy,sNy+OLy
144 DO i=1-OLx+1,sNx+OLx ! NOTE range
145 C by averaging
146 dxC(i,j,bi,bj) = 0.5 _d 0*(dxF(i,j,bi,bj)+dxF(i-1,j,bi,bj))
147 C by formula
148 c lat = 0.5*(yC(i,j,bi,bj)+yC(i-1,j,bi,bj))
149 c dlon = 0.5*( delXloc(i) + delXloc(i-1) )
150 c dxC(i,j,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
151 C by difference
152 c lat = 0.5*(yC(i,j,bi,bj)+yC(i-1,j,bi,bj))
153 c dlon = (xC(i,j,bi,bj)-xC(i-1,j,bi,bj))
154 c dxC(i,j,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
155 ENDDO
156 ENDDO
157
158 C-- Calculate [dyC], meridional length between cell centers
159 DO j=1-OLy+1,sNy+OLy ! NOTE range
160 DO i=1-OLx,sNx+OLx
161 C by averaging
162 dyC(i,j,bi,bj) = 0.5 _d 0*(dyF(i,j,bi,bj)+dyF(i,j-1,bi,bj))
163 C by formula
164 c dlat = 0.5*( delYloc(j) + delYloc(j-1) )
165 c dyC(i,j,bi,bj) = rSphere*dlat*deg2rad
166 C by difference
167 c dlat = (yC(i,j,bi,bj)-yC(i,j-1,bi,bj))
168 c dyC(i,j,bi,bj) = rSphere*dlat*deg2rad
169 ENDDO
170 ENDDO
171
172 C-- Calculate [dxV,dyU], length between velocity points (through corners)
173 DO j=1-OLy+1,sNy+OLy ! NOTE range
174 DO i=1-OLx+1,sNx+OLx ! NOTE range
175 C by averaging (method I)
176 dxV(i,j,bi,bj) = 0.5 _d 0*(dxG(i,j,bi,bj)+dxG(i-1,j,bi,bj))
177 dyU(i,j,bi,bj) = 0.5 _d 0*(dyG(i,j,bi,bj)+dyG(i,j-1,bi,bj))
178 C by averaging (method II)
179 c dxV(i,j,bi,bj) = 0.5*(dxG(i,j,bi,bj)+dxG(i-1,j,bi,bj))
180 c dyU(i,j,bi,bj) = 0.5*(dyC(i,j,bi,bj)+dyC(i-1,j,bi,bj))
181 ENDDO
182 ENDDO
183
184 C-- Calculate vertical face area (tracer cells)
185 DO j=1-OLy,sNy+OLy
186 DO i=1-OLx,sNx+OLx
187 lat=0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
188 dlon = delXloc(i)
189 dlat = delYloc(j)
190 rA(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
191 & *ABS( SIN((lat+dlat)*deg2rad)-SIN(lat*deg2rad) )
192 #ifdef USE_BACKWARD_COMPATIBLE_GRID
193 lat = yC(i,j,bi,bj) - delYloc(j)*0.5 _d 0
194 dlat= yC(i,j,bi,bj) + delYloc(j)*0.5 _d 0
195 rA(i,j,bi,bj) = dyF(i,j,bi,bj)
196 & *rSphere*(SIN(dlat*deg2rad)-SIN(lat*deg2rad))
197 #endif /* USE_BACKWARD_COMPATIBLE_GRID */
198 ENDDO
199 ENDDO
200
201 C-- Calculate vertical face area (u cells)
202 DO j=1-OLy,sNy+OLy
203 DO i=1-OLx+1,sNx+OLx ! NOTE range
204 C by averaging
205 rAw(i,j,bi,bj) = 0.5 _d 0*(rA(i,j,bi,bj)+rA(i-1,j,bi,bj))
206 C by formula
207 c lat=yGloc(i,j)
208 c dlon = 0.5*( delXloc(i) + delXloc(i-1) )
209 c dlat = delYloc(j)
210 c rAw(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
211 c & *abs( sin((lat+dlat)*deg2rad)-sin(lat*deg2rad) )
212 ENDDO
213 ENDDO
214
215 C-- Calculate vertical face area (v cells)
216 DO j=1-OLy,sNy+OLy
217 DO i=1-OLx,sNx+OLx
218 C by formula
219 lat=yC(i,j,bi,bj)
220 dlon = delXloc(i)
221 dlat = 0.5 _d 0*( delYloc(j) + delYloc(j-1) )
222 #ifdef USE_BACKWARD_COMPATIBLE_GRID
223 dlat= delYloc(j)
224 #endif /* USE_BACKWARD_COMPATIBLE_GRID */
225 rAs(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
226 & *ABS( SIN(lat*deg2rad)-SIN((lat-dlat)*deg2rad) )
227 IF (ABS(lat).GT.90..OR.ABS(lat-dlat).GT.90.) rAs(i,j,bi,bj)=0.
228 ENDDO
229 ENDDO
230
231 C-- Calculate vertical face area (vorticity points)
232 DO j=1-OLy,sNy+OLy
233 DO i=1-OLx,sNx+OLx
234 C by formula
235 lat = 0.5 _d 0*(yGloc(i,j)+yGloc(i,j+1))
236 dlon = 0.5 _d 0*( delXloc(i) + delXloc(i-1) )
237 dlat = 0.5 _d 0*( delYloc(j) + delYloc(j-1) )
238 rAz(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
239 & *ABS( SIN(lat*deg2rad)-SIN((lat-dlat)*deg2rad) )
240 IF (ABS(lat).GT.90..OR.ABS(lat-dlat).GT.90.) rAz(i,j,bi,bj)=0.
241 ENDDO
242 ENDDO
243
244 C-- Calculate trigonometric terms & grid orientation:
245 DO j=1-OLy,sNy+OLy
246 DO i=1-OLx,sNx+OLx
247 lat=0.5 _d 0*(yGloc(i,j)+yGloc(i,j+1))
248 tanPhiAtU(i,j,bi,bj)=TAN(lat*deg2rad)
249 lat=0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
250 tanPhiAtV(i,j,bi,bj)=TAN(lat*deg2rad)
251 C Note: this is now done earlier in main S/R INI_GRID
252 c angleCosC(i,j,bi,bj) = 1.
253 c angleSinC(i,j,bi,bj) = 0.
254 ENDDO
255 ENDDO
256
257 C-- Cosine(lat) scaling
258 DO j=1-OLy,sNy+OLy
259 i = 1
260 IF (cosPower.NE.0.) THEN
261 lat = 0.5 _d 0*(yGloc(i,j)+yGloc(i,j+1))
262 cosFacU(j,bi,bj) = ABS( COS(lat*deg2rad) )**cosPower
263 lat = 0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
264 cosFacV(j,bi,bj) = ABS( COS(lat*deg2rad) )**cosPower
265 sqcosFacU(j,bi,bj) = SQRT(cosFacU(j,bi,bj))
266 sqcosFacV(j,bi,bj) = SQRT(cosFacV(j,bi,bj))
267 ELSE
268 cosFacU(j,bi,bj) = 1.
269 cosFacV(j,bi,bj) = 1.
270 sqcosFacU(j,bi,bj)=1.
271 sqcosFacV(j,bi,bj)=1.
272 ENDIF
273 ENDDO
274
275 C-- end bi,bj loops
276 ENDDO
277 ENDDO
278
279 IF ( rotateGrid ) THEN
280 CALL ROTATE_SPHERICAL_POLAR_GRID( xC, yC, myThid )
281 CALL ROTATE_SPHERICAL_POLAR_GRID( xG, yG, myThid )
282 skipCalcAngleC = .FALSE.
283 CALL CALC_GRID_ANGLES( skipCalcAngleC, myThid )
284 ENDIF
285
286 RETURN
287 END

  ViewVC Help
Powered by ViewVC 1.1.22