/[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.27 - (show annotations) (download)
Sat Apr 17 18:25:12 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.26: +172 -167 lines
add code for Exch2 IO layout:
 (not always compatible with delX,delY setting; commented out for now)
add some _d 0 ; clean-up variable description.

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_spherical_polar_grid.F,v 1.26 2009/01/27 15:35:27 jmc Exp $
2 C $Name: $
3
4 c#include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 #undef USE_BACKWARD_COMPATIBLE_GRID
8
9 CBOP
10 C !ROUTINE: INI_SPHERICAL_POLAR_GRID
11 C !INTERFACE:
12 SUBROUTINE INI_SPHERICAL_POLAR_GRID( myThid )
13
14 C !DESCRIPTION: \bv
15 C *==========================================================*
16 C | SUBROUTINE INI_SPHERICAL_POLAR_GRID
17 C | o Initialise model coordinate system arrays
18 C *==========================================================*
19 C | These arrays are used throughout the code in evaluating
20 C | gradients, integrals and spatial avarages. This routine
21 C | is called separately by each thread and initialise only
22 C | the region of the domain it is "responsible" for.
23 C | Under the spherical polar grid mode primitive distances
24 C | in X and Y are in degrees. Distance in Z are in m or Pa
25 C | depending on the vertical gridding mode.
26 C *==========================================================*
27 C \ev
28
29 C !USES:
30 IMPLICIT NONE
31 C === Global variables ===
32 #include "SIZE.h"
33 #include "EEPARAMS.h"
34 #include "PARAMS.h"
35 #include "GRID.h"
36 c#ifdef ALLOW_EXCH2
37 c#include "W2_EXCH2_SIZE.h"
38 c#include "W2_EXCH2_TOPOLOGY.h"
39 c#include "W2_EXCH2_PARAMS.h"
40 c#endif /* ALLOW_EXCH2 */
41
42 C !INPUT/OUTPUT PARAMETERS:
43 C == Routine arguments ==
44 C myThid :: my Thread Id Number
45 INTEGER myThid
46
47 C !LOCAL VARIABLES:
48 C == Local variables ==
49 C xG0,yG0 :: coordinate of South-West tile-corner
50 C iG, jG :: Global coordinate index. Usually used to hold
51 C :: the south-west global coordinate of a tile.
52 C lat :: Temporary variables used to hold latitude values.
53 C bi,bj :: tile indices
54 C i, j :: loop counters
55 INTEGER iG, jG
56 INTEGER bi, bj
57 INTEGER i, j
58 _RL lat, dlat, dlon, xG0, yG0
59
60 C "Long" real for temporary coordinate calculation
61 C NOTICE the extended range of indices!!
62 _RL xGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
63 _RL yGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
64
65 C The functions iGl, jGl return the "global" index with valid values beyond
66 C halo regions
67 C cnh wrote:
68 C > I dont understand why we would ever have to multiply the
69 C > overlap by the total domain size e.g
70 C > OLx*Nx, OLy*Ny.
71 C > Can anybody explain? Lines are in ini_spherical_polar_grid.F.
72 C > Surprised the code works if its wrong, so I am puzzled.
73 C jmc replied:
74 C Yes, I can explain this since I put this modification to work
75 C with small domain (where Oly > Ny, as for instance, zonal-average
76 C case):
77 C This has no effect on the acuracy of the evaluation of iGl(I,bi)
78 C and jGl(j,bj) since we take mod(a+OLx*Nx,Nx) and mod(b+OLy*Ny,Ny).
79 C But in case a or b is negative, then the FORTRAN function "mod"
80 C does not return the matematical value of the "modulus" function,
81 C and this is not good for your purpose.
82 C This is why I add +OLx*Nx and +OLy*Ny to be sure that the 1rst
83 C argument of the mod function is positive.
84 INTEGER iGl,jGl
85 iGl(i,bi) = 1+MOD(myXGlobalLo-1+(bi-1)*sNx+i+Olx*Nx-1,Nx)
86 jGl(j,bj) = 1+MOD(myYGlobalLo-1+(bj-1)*sNy+j+Oly*Ny-1,Ny)
87 c#ifdef ALLOW_EXCH2
88 c INTEGER tN
89 c#endif /* ALLOW_EXCH2 */
90 CEOP
91
92 C For each tile ...
93 DO bj = myByLo(myThid), myByHi(myThid)
94 DO bi = myBxLo(myThid), myBxHi(myThid)
95
96 C-- "Global" index (place holder)
97 jG = myYGlobalLo + (bj-1)*sNy
98 iG = myXGlobalLo + (bi-1)*sNx
99 c#ifdef ALLOW_EXCH2
100 c IF ( W2_useE2ioLayOut ) THEN
101 cC- note: does not work for non-uniform delX or delY
102 c tN = W2_myTileList(bi,bj)
103 c iG = exch2_txGlobalo(tN)
104 c jG = exch2_tyGlobalo(tN)
105 c ENDIF
106 c#endif /* ALLOW_EXCH2 */
107
108 C-- First find coordinate of tile corner (meaning outer corner of halo)
109 xG0 = xgOrigin
110 C Find the X-coordinate of the outer grid-line of the "real" tile
111 DO i=1, iG-1
112 xG0 = xG0 + delX(i)
113 ENDDO
114 C Back-step to the outer grid-line of the "halo" region
115 DO i=1, Olx
116 xG0 = xG0 - delX( 1+MOD(Olx*Nx-1+iG-i,Nx) )
117 ENDDO
118 C Find the Y-coordinate of the outer grid-line of the "real" tile
119 yG0 = ygOrigin
120 DO j=1, jG-1
121 yG0 = yG0 + delY(j)
122 ENDDO
123 C Back-step to the outer grid-line of the "halo" region
124 DO j=1, Oly
125 yG0 = yG0 - delY( 1+MOD(Oly*Ny-1+jG-j,Ny) )
126 ENDDO
127
128 C-- Calculate coordinates of cell corners for N+1 grid-lines
129 DO j=1-Oly,sNy+Oly +1
130 xGloc(1-Olx,j) = xG0
131 DO i=1-Olx,sNx+Olx
132 c xGloc(i+1,j) = xGloc(i,j) + delX(1+mod(Nx-1+iG-1+i,Nx))
133 xGloc(i+1,j) = xGloc(i,j) + delX( iGl(i,bi) )
134 ENDDO
135 ENDDO
136 DO i=1-Olx,sNx+Olx +1
137 yGloc(i,1-Oly) = yG0
138 DO j=1-Oly,sNy+Oly
139 c yGloc(i,j+1) = yGloc(i,j) + delY(1+mod(Ny-1+jG-1+j,Ny))
140 yGloc(i,j+1) = yGloc(i,j) + delY( jGl(j,bj) )
141 ENDDO
142 ENDDO
143
144 C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
145 DO j=1-Oly,sNy+Oly
146 DO i=1-Olx,sNx+Olx
147 xG(i,j,bi,bj) = xGloc(i,j)
148 yG(i,j,bi,bj) = yGloc(i,j)
149 ENDDO
150 ENDDO
151
152 C-- Calculate [xC,yC], coordinates of cell centers
153 DO j=1-Oly,sNy+Oly
154 DO i=1-Olx,sNx+Olx
155 C by averaging
156 xC(i,j,bi,bj) = 0.25 _d 0*(
157 & xGloc(i,j)+xGloc(i+1,j)+xGloc(i,j+1)+xGloc(i+1,j+1) )
158 yC(i,j,bi,bj) = 0.25 _d 0*(
159 & yGloc(i,j)+yGloc(i+1,j)+yGloc(i,j+1)+yGloc(i+1,j+1) )
160 ENDDO
161 ENDDO
162
163 C-- Calculate [dxF,dyF], lengths between cell faces (through center)
164 DO j=1-Oly,sNy+Oly
165 DO i=1-Olx,sNx+Olx
166 C by averaging
167 c dxF(i,j,bi,bj) = 0.5*(dxG(i,j,bi,bj)+dxG(i,j+1,bi,bj))
168 c dyF(i,j,bi,bj) = 0.5*(dyG(i,j,bi,bj)+dyG(i+1,j,bi,bj))
169 C by formula
170 lat = yC(i,j,bi,bj)
171 dlon = delX( iGl(i,bi) )
172 dlat = delY( jGl(j,bj) )
173 dxF(i,j,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
174 #ifdef USE_BACKWARD_COMPATIBLE_GRID
175 dxF(i,j,bi,bj) = delX(iGl(i,bi))*deg2rad*rSphere*
176 & COS(yC(i,j,bi,bj)*deg2rad)
177 #endif /* USE_BACKWARD_COMPATIBLE_GRID */
178 dyF(i,j,bi,bj) = rSphere*dlat*deg2rad
179 ENDDO
180 ENDDO
181
182 C-- Calculate [dxG,dyG], lengths along cell boundaries
183 DO j=1-Oly,sNy+Oly
184 DO i=1-Olx,sNx+Olx
185 C by averaging
186 c dxG(i,j,bi,bj) = 0.5*(dxF(i,j,bi,bj)+dxF(i,j-1,bi,bj))
187 c dyG(i,j,bi,bj) = 0.5*(dyF(i,j,bi,bj)+dyF(i-1,j,bi,bj))
188 C by formula
189 lat = 0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
190 dlon = delX( iGl(i,bi) )
191 dlat = delY( jGl(j,bj) )
192 dxG(i,j,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
193 if (dxG(i,j,bi,bj).LT.1.) dxG(i,j,bi,bj)=0.
194 dyG(i,j,bi,bj) = rSphere*dlat*deg2rad
195 ENDDO
196 ENDDO
197
198 C-- The following arrays are not defined in some parts of the halo
199 C region. We set them to zero here for safety. If they are ever
200 C referred to, especially in the denominator then it is a mistake!
201 DO j=1-Oly,sNy+Oly
202 DO i=1-Olx,sNx+Olx
203 dxC(i,j,bi,bj) = 0.
204 dyC(i,j,bi,bj) = 0.
205 dxV(i,j,bi,bj) = 0.
206 dyU(i,j,bi,bj) = 0.
207 rAw(i,j,bi,bj) = 0.
208 rAs(i,j,bi,bj) = 0.
209 ENDDO
210 ENDDO
211
212 C-- Calculate [dxC], zonal length between cell centers
213 DO j=1-Oly,sNy+Oly
214 DO i=1-Olx+1,sNx+Olx ! NOTE range
215 C by averaging
216 dxC(i,j,bi,bj) = 0.5 _d 0*(dxF(i,j,bi,bj)+dxF(i-1,j,bi,bj))
217 C by formula
218 c lat = 0.5*(yC(i,j,bi,bj)+yC(i-1,j,bi,bj))
219 c dlon = 0.5*(delX( iGl(i,bi) ) + delX( iGl(i-1,bi) ))
220 c dxC(i,j,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
221 C by difference
222 c lat = 0.5*(yC(i,j,bi,bj)+yC(i-1,j,bi,bj))
223 c dlon = (xC(i,j,bi,bj)+xC(i-1,j,bi,bj))
224 c dxC(i,j,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
225 ENDDO
226 ENDDO
227
228 C-- Calculate [dyC], meridional length between cell centers
229 DO j=1-Oly+1,sNy+Oly ! NOTE range
230 DO i=1-Olx,sNx+Olx
231 C by averaging
232 dyC(i,j,bi,bj) = 0.5 _d 0*(dyF(i,j,bi,bj)+dyF(i,j-1,bi,bj))
233 C by formula
234 c dlat = 0.5*(delY( jGl(j,bj) ) + delY( jGl(j-1,bj) ))
235 c dyC(i,j,bi,bj) = rSphere*dlat*deg2rad
236 C by difference
237 c dlat = (yC(i,j,bi,bj)+yC(i,j-1,bi,bj))
238 c dyC(i,j,bi,bj) = rSphere*dlat*deg2rad
239 ENDDO
240 ENDDO
241
242 C-- Calculate [dxV,dyU], length between velocity points (through corners)
243 DO j=1-Oly+1,sNy+Oly ! NOTE range
244 DO i=1-Olx+1,sNx+Olx ! NOTE range
245 C by averaging (method I)
246 dxV(i,j,bi,bj) = 0.5 _d 0*(dxG(i,j,bi,bj)+dxG(i-1,j,bi,bj))
247 dyU(i,j,bi,bj) = 0.5 _d 0*(dyG(i,j,bi,bj)+dyG(i,j-1,bi,bj))
248 C by averaging (method II)
249 c dxV(i,j,bi,bj) = 0.5*(dxG(i,j,bi,bj)+dxG(i-1,j,bi,bj))
250 c dyU(i,j,bi,bj) = 0.5*(dyC(i,j,bi,bj)+dyC(i-1,j,bi,bj))
251 ENDDO
252 ENDDO
253
254 C-- Calculate vertical face area (tracer cells)
255 DO j=1-Oly,sNy+Oly
256 DO i=1-Olx,sNx+Olx
257 lat=0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
258 dlon=delX( iGl(i,bi) )
259 dlat=delY( jGl(j,bj) )
260 rA(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
261 & *ABS( SIN((lat+dlat)*deg2rad)-SIN(lat*deg2rad) )
262 #ifdef USE_BACKWARD_COMPATIBLE_GRID
263 lat=yC(i,j,bi,bj)-delY( jGl(j,bj) )*0.5 _d 0
264 lon=yC(i,j,bi,bj)+delY( jGl(j,bj) )*0.5 _d 0
265 rA(i,j,bi,bj) = dyF(i,j,bi,bj)
266 & *rSphere*(SIN(lon*deg2rad)-SIN(lat*deg2rad))
267 #endif /* USE_BACKWARD_COMPATIBLE_GRID */
268 ENDDO
269 ENDDO
270
271 C-- Calculate vertical face area (u cells)
272 DO j=1-Oly,sNy+Oly
273 DO i=1-Olx+1,sNx+Olx ! NOTE range
274 C by averaging
275 rAw(i,j,bi,bj) = 0.5 _d 0*(rA(i,j,bi,bj)+rA(i-1,j,bi,bj))
276 C by formula
277 c lat=yGloc(i,j)
278 c dlon=0.5*( delX( iGl(i,bi) ) + delX( iGl(i-1,bi) ) )
279 c dlat=delY( jGl(j,bj) )
280 c rAw(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
281 c & *abs( sin((lat+dlat)*deg2rad)-sin(lat*deg2rad) )
282 ENDDO
283 ENDDO
284
285 C-- Calculate vertical face area (v cells)
286 DO j=1-Oly,sNy+Oly
287 DO i=1-Olx,sNx+Olx
288 C by formula
289 lat=yC(i,j,bi,bj)
290 dlon=delX( iGl(i,bi) )
291 dlat=0.5 _d 0*( delY( jGl(j,bj) ) + delY( jGl(j-1,bj) ) )
292 rAs(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
293 & *ABS( SIN(lat*deg2rad)-SIN((lat-dlat)*deg2rad) )
294 #ifdef USE_BACKWARD_COMPATIBLE_GRID
295 lon=yC(i,j,bi,bj)-delY( jGl(j,bj) )
296 lat=yC(i,j,bi,bj)
297 rAs(i,j,bi,bj) = rSphere*delX(iGl(i,bi))*deg2rad
298 & *rSphere*(SIN(lat*deg2rad)-SIN(lon*deg2rad))
299 #endif /* USE_BACKWARD_COMPATIBLE_GRID */
300 IF (ABS(lat).GT.90..OR.ABS(lat-dlat).GT.90.) rAs(i,j,bi,bj)=0.
301 ENDDO
302 ENDDO
303
304 C-- Calculate vertical face area (vorticity points)
305 DO j=1-Oly,sNy+Oly
306 DO i=1-Olx,sNx+Olx
307 C by formula
308 lat =0.5 _d 0*(yGloc(i,j)+yGloc(i,j+1))
309 dlon=0.5 _d 0*( delX( iGl(i,bi) ) + delX( iGl(i-1,bi) ) )
310 dlat=0.5 _d 0*( delY( jGl(j,bj) ) + delY( jGl(j-1,bj) ) )
311 rAz(i,j,bi,bj) = rSphere*rSphere*dlon*deg2rad
312 & *ABS( SIN(lat*deg2rad)-SIN((lat-dlat)*deg2rad) )
313 IF (ABS(lat).GT.90..OR.ABS(lat-dlat).GT.90.) rAz(i,j,bi,bj)=0.
314 ENDDO
315 ENDDO
316
317 C-- Calculate trigonometric terms & grid orientation:
318 DO j=1-Oly,sNy+Oly
319 DO i=1-Olx,sNx+Olx
320 lat=0.5 _d 0*(yGloc(i,j)+yGloc(i,j+1))
321 tanPhiAtU(i,j,bi,bj)=TAN(lat*deg2rad)
322 lat=0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
323 tanPhiAtV(i,j,bi,bj)=TAN(lat*deg2rad)
324 angleCosC(i,j,bi,bj) = 1.
325 angleSinC(i,j,bi,bj) = 0.
326 ENDDO
327 ENDDO
328
329 C-- Cosine(lat) scaling
330 DO j=1-OLy,sNy+OLy
331 jG = myYGlobalLo + (bj-1)*sNy + j-1
332 jG = MIN(MAX(1,jG),Ny)
333 IF (cosPower.NE.0.) THEN
334 cosFacU(j,bi,bj)=COS(yC(1,j,bi,bj)*deg2rad)
335 & **cosPower
336 cosFacV(j,bi,bj)=COS((yC(1,j,bi,bj)-0.5*delY(jG))*deg2rad)
337 & **cosPower
338 cosFacU(j,bi,bj)=ABS(cosFacU(j,bi,bj))
339 cosFacV(j,bi,bj)=ABS(cosFacV(j,bi,bj))
340 sqcosFacU(j,bi,bj)=SQRT(cosFacU(j,bi,bj))
341 sqcosFacV(j,bi,bj)=SQRT(cosFacV(j,bi,bj))
342 ELSE
343 cosFacU(j,bi,bj)=1.
344 cosFacV(j,bi,bj)=1.
345 sqcosFacU(j,bi,bj)=1.
346 sqcosFacV(j,bi,bj)=1.
347 ENDIF
348 ENDDO
349
350 ENDDO ! bi
351 ENDDO ! bj
352
353 IF ( rotateGrid ) THEN
354 CALL ROTATE_SPHERICAL_POLAR_GRID( xC, yC, myThid )
355 CALL ROTATE_SPHERICAL_POLAR_GRID( xG, yG, myThid )
356 CALL CALC_ANGLES( myThid )
357 ENDIF
358
359 RETURN
360 END

  ViewVC Help
Powered by ViewVC 1.1.22