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

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

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


Revision 1.18 - (hide annotations) (download)
Tue May 29 14:01:37 2001 UTC (22 years, 11 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5, checkpoint40
Changes since 1.17: +40 -2 lines
Merge from branch pre38:
 o essential mods for cubed sphere
 o debugged atmosphere, dynamcis + physics (aim)
 o new packages (mom_vecinv, mom_fluxform, ...)

1 adcroft 1.18 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_spherical_polar_grid.F,v 1.17.2.3 2001/04/08 21:58:27 cnh Exp $
2 cnh 1.17 C $Name: $
3 cnh 1.1
4 cnh 1.10 #include "CPP_OPTIONS.h"
5 cnh 1.1
6 adcroft 1.15 #undef USE_BACKWARD_COMPATIBLE_GRID
7    
8 cnh 1.1 CStartOfInterface
9     SUBROUTINE INI_SPHERICAL_POLAR_GRID( myThid )
10     C /==========================================================\
11     C | SUBROUTINE INI_SPHERICAL_POLAR_GRID |
12     C | o Initialise model coordinate system |
13     C |==========================================================|
14     C | These arrays are used throughout the code in evaluating |
15     C | gradients, integrals and spatial avarages. This routine |
16     C | is called separately by each thread and initialise only |
17     C | the region of the domain it is "responsible" for. |
18     C | Notes: |
19     C | Two examples are included. One illustrates the |
20     C | initialisation of a cartesian grid. The other shows the |
21     C | inialisation of a spherical polar grid. Other orthonormal|
22     C | grids can be fitted into this design. In this case |
23     C | custom metric terms also need adding to account for the |
24     C | projections of velocity vectors onto these grids. |
25     C | The structure used here also makes it possible to |
26     C | implement less regular grid mappings. In particular |
27     C | o Schemes which leave out blocks of the domain that are |
28     C | all land could be supported. |
29     C | o Multi-level schemes such as icosohedral or cubic |
30     C | grid projections onto a sphere can also be fitted |
31     C | within the strategy we use. |
32     C | Both of the above also require modifying the support |
33     C | routines that map computational blocks to simulation |
34     C | domain blocks. |
35     C | Under the spherical polar grid mode primitive distances |
36     C | in X and Y are in degrees. Distance in Z are in m or Pa |
37     C | depending on the vertical gridding mode. |
38     C \==========================================================/
39 adcroft 1.12 IMPLICIT NONE
40 cnh 1.1
41     C === Global variables ===
42     #include "SIZE.h"
43     #include "EEPARAMS.h"
44     #include "PARAMS.h"
45     #include "GRID.h"
46    
47     C == Routine arguments ==
48     C myThid - Number of this instance of INI_CARTESIAN_GRID
49     INTEGER myThid
50     CEndOfInterface
51    
52     C == Local variables ==
53     C xG, yG - Global coordinate location.
54     C xBase - South-west corner location for process.
55     C yBase
56 adcroft 1.15 C zUpper - Work arrays for upper and lower
57     C zLower cell-face heights.
58     C phi - Temporary scalar
59 cnh 1.1 C iG, jG - Global coordinate index. Usually used to hold
60     C the south-west global coordinate of a tile.
61     C bi,bj - Loop counters
62     C zUpper - Temporary arrays holding z coordinates of
63     C zLower upper and lower faces.
64     C xBase - Lower coordinate for this threads cells
65     C yBase
66     C lat, latN, - Temporary variables used to hold latitude
67     C latS values.
68     C I,J,K
69     INTEGER iG, jG
70     INTEGER bi, bj
71 adcroft 1.14 INTEGER I, J
72 adcroft 1.15 _RL lat, dlat, dlon, xG0, yG0
73    
74    
75     C "Long" real for temporary coordinate calculation
76     C NOTICE the extended range of indices!!
77     _RL xGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
78     _RL yGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
79    
80 adcroft 1.18 C The functions iGl, jGl return the "global" index with valid values beyond
81 adcroft 1.15 C halo regions
82 adcroft 1.18 C cnh wrote:
83     C > I don't understand why we would ever have to multiply the
84     C > overlap by the total domain size e.g
85     C > OLx*Nx, OLy*Ny.
86     C > Can anybody explain? Lines are in ini_spherical_polar_grid.F.
87     C > Surprised the code works if its wrong, so I am puzzled.
88     C jmc relied:
89     C Yes, I can explain this since I put this modification to work
90     C with small domain (where Oly > Ny, as for instance, zonal-average
91     C case):
92     C This has no effect on the acuracy of the evaluation of iGl(I,bi)
93     C and jGl(J,bj) since we take mod(a+OLx*Nx,Nx) and mod(b+OLy*Ny,Ny).
94     C But in case a or b is negative, then the FORTRAN function "mod"
95     C does not return the matematical value of the "modulus" function,
96     C and this is not good for your purpose.
97     C This is why I add +OLx*Nx and +OLy*Ny to be sure that the 1rst
98     C argument of the mod function is positive.
99 adcroft 1.15 INTEGER iGl,jGl
100     iGl(I,bi) = 1+mod(myXGlobalLo-1+(bi-1)*sNx+I+Olx*Nx-1,Nx)
101     jGl(J,bj) = 1+mod(myYGlobalLo-1+(bj-1)*sNy+J+Oly*Ny-1,Ny)
102 cnh 1.1
103 adcroft 1.18
104 adcroft 1.15 C For each tile ...
105 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
106     DO bi = myBxLo(myThid), myBxHi(myThid)
107 adcroft 1.15
108     C-- "Global" index (place holder)
109     jG = myYGlobalLo + (bj-1)*sNy
110 cnh 1.1 iG = myXGlobalLo + (bi-1)*sNx
111    
112 adcroft 1.15 C-- First find coordinate of tile corner (meaning outer corner of halo)
113     xG0 = thetaMin
114     C Find the X-coordinate of the outer grid-line of the "real" tile
115     DO i=1, iG-1
116     xG0 = xG0 + delX(i)
117     ENDDO
118     C Back-step to the outer grid-line of the "halo" region
119     DO i=1, Olx
120     xG0 = xG0 - delX( 1+mod(Olx*Nx-1+iG-i,Nx) )
121     ENDDO
122     C Find the Y-coordinate of the outer grid-line of the "real" tile
123     yG0 = phiMin
124     DO j=1, jG-1
125     yG0 = yG0 + delY(j)
126     ENDDO
127     C Back-step to the outer grid-line of the "halo" region
128     DO j=1, Oly
129     yG0 = yG0 - delY( 1+mod(Oly*Ny-1+jG-j,Ny) )
130     ENDDO
131    
132     C-- Calculate coordinates of cell corners for N+1 grid-lines
133     DO J=1-Oly,sNy+Oly +1
134     xGloc(1-Olx,J) = xG0
135     DO I=1-Olx,sNx+Olx
136     c xGloc(I+1,J) = xGloc(I,J) + delX(1+mod(Nx-1+iG-1+i,Nx))
137     xGloc(I+1,J) = xGloc(I,J) + delX( iGl(I,bi) )
138     ENDDO
139     ENDDO
140     DO I=1-Olx,sNx+Olx +1
141     yGloc(I,1-Oly) = yG0
142     DO J=1-Oly,sNy+Oly
143     c yGloc(I,J+1) = yGloc(I,J) + delY(1+mod(Ny-1+jG-1+j,Ny))
144     yGloc(I,J+1) = yGloc(I,J) + delY( jGl(J,bj) )
145     ENDDO
146     ENDDO
147    
148     C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
149     DO J=1-Oly,sNy+Oly
150     DO I=1-Olx,sNx+Olx
151     xG(I,J,bi,bj) = xGloc(I,J)
152     yG(I,J,bi,bj) = yGloc(I,J)
153     ENDDO
154     ENDDO
155    
156     C-- Calculate [xC,yC], coordinates of cell centers
157     DO J=1-Oly,sNy+Oly
158     DO I=1-Olx,sNx+Olx
159     C by averaging
160     xC(I,J,bi,bj) = 0.25*(
161     & xGloc(I,J)+xGloc(I+1,J)+xGloc(I,J+1)+xGloc(I+1,J+1) )
162     yC(I,J,bi,bj) = 0.25*(
163     & yGloc(I,J)+yGloc(I+1,J)+yGloc(I,J+1)+yGloc(I+1,J+1) )
164     ENDDO
165     ENDDO
166    
167     C-- Calculate [dxF,dyF], lengths between cell faces (through center)
168     DO J=1-Oly,sNy+Oly
169     DO I=1-Olx,sNx+Olx
170     C by averaging
171     c dXF(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I,J+1,bi,bj))
172     c dYF(I,J,bi,bj) = 0.5*(dYG(I,J,bi,bj)+dYG(I+1,J,bi,bj))
173     C by formula
174     lat = yC(I,J,bi,bj)
175     dlon = delX( iGl(I,bi) )
176     dlat = delY( jGl(J,bj) )
177     dXF(I,J,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
178     #ifdef USE_BACKWARD_COMPATIBLE_GRID
179     dXF(I,J,bi,bj) = delX(iGl(I,bi))*deg2rad*rSphere*
180     & COS(yc(I,J,bi,bj)*deg2rad)
181     #endif /* USE_BACKWARD_COMPATIBLE_GRID */
182     dYF(I,J,bi,bj) = rSphere*dlat*deg2rad
183     ENDDO
184     ENDDO
185    
186     C-- Calculate [dxG,dyG], lengths along cell boundaries
187     DO J=1-Oly,sNy+Oly
188     DO I=1-Olx,sNx+Olx
189     C by averaging
190     c dXG(I,J,bi,bj) = 0.5*(dXF(I,J,bi,bj)+dXF(I,J-1,bi,bj))
191     c dYG(I,J,bi,bj) = 0.5*(dYF(I,J,bi,bj)+dYF(I-1,J,bi,bj))
192     C by formula
193     lat = 0.5*(yGloc(I,J)+yGloc(I+1,J))
194     dlon = delX( iGl(I,bi) )
195     dlat = delY( jGl(J,bj) )
196     dXG(I,J,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
197 adcroft 1.18 if (dXG(I,J,bi,bj).LT.1.) dXG(I,J,bi,bj)=0.
198 adcroft 1.15 dYG(I,J,bi,bj) = rSphere*dlat*deg2rad
199     ENDDO
200     ENDDO
201    
202     C-- The following arrays are not defined in some parts of the halo
203     C region. We set them to zero here for safety. If they are ever
204     C referred to, especially in the denominator then it is a mistake!
205     DO J=1-Oly,sNy+Oly
206     DO I=1-Olx,sNx+Olx
207     dXC(I,J,bi,bj) = 0.
208     dYC(I,J,bi,bj) = 0.
209     dXV(I,J,bi,bj) = 0.
210     dYU(I,J,bi,bj) = 0.
211     rAw(I,J,bi,bj) = 0.
212     rAs(I,J,bi,bj) = 0.
213     ENDDO
214     ENDDO
215    
216     C-- Calculate [dxC], zonal length between cell centers
217     DO J=1-Oly,sNy+Oly
218     DO I=1-Olx+1,sNx+Olx ! NOTE range
219     C by averaging
220     dXC(I,J,bi,bj) = 0.5D0*(dXF(I,J,bi,bj)+dXF(I-1,J,bi,bj))
221     C by formula
222     c lat = 0.5*(yC(I,J,bi,bj)+yC(I-1,J,bi,bj))
223     c dlon = 0.5*(delX( iGl(I,bi) ) + delX( iGl(I-1,bi) ))
224     c dXC(I,J,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
225     C by difference
226     c lat = 0.5*(yC(I,J,bi,bj)+yC(I-1,J,bi,bj))
227     c dlon = (xC(I,J,bi,bj)+xC(I-1,J,bi,bj))
228     c dXC(I,J,bi,bj) = rSphere*COS(deg2rad*lat)*dlon*deg2rad
229 cnh 1.1 ENDDO
230     ENDDO
231 adcroft 1.15
232     C-- Calculate [dyC], meridional length between cell centers
233     DO J=1-Oly+1,sNy+Oly ! NOTE range
234     DO I=1-Olx,sNx+Olx
235     C by averaging
236     dYC(I,J,bi,bj) = 0.5*(dYF(I,J,bi,bj)+dYF(I,J-1,bi,bj))
237     C by formula
238     c dlat = 0.5*(delY( jGl(J,bj) ) + delY( jGl(J-1,bj) ))
239     c dYC(I,J,bi,bj) = rSphere*dlat*deg2rad
240     C by difference
241     c dlat = (yC(I,J,bi,bj)+yC(I,J-1,bi,bj))
242     c dYC(I,J,bi,bj) = rSphere*dlat*deg2rad
243 cnh 1.1 ENDDO
244     ENDDO
245 adcroft 1.15
246     C-- Calculate [dxV,dyU], length between velocity points (through corners)
247     DO J=1-Oly+1,sNy+Oly ! NOTE range
248     DO I=1-Olx+1,sNx+Olx ! NOTE range
249     C by averaging (method I)
250     dXV(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I-1,J,bi,bj))
251     dYU(I,J,bi,bj) = 0.5*(dYG(I,J,bi,bj)+dYG(I,J-1,bi,bj))
252     C by averaging (method II)
253     c dXV(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I-1,J,bi,bj))
254     c dYU(I,J,bi,bj) = 0.5*(dYC(I,J,bi,bj)+dYC(I-1,J,bi,bj))
255 cnh 1.1 ENDDO
256     ENDDO
257 adcroft 1.15
258     C-- Calculate vertical face area (tracer cells)
259     DO J=1-Oly,sNy+Oly
260     DO I=1-Olx,sNx+Olx
261     lat=0.5*(yGloc(I,J)+yGloc(I+1,J))
262     dlon=delX( iGl(I,bi) )
263     dlat=delY( jGl(J,bj) )
264     rA(I,J,bi,bj) = rSphere*rSphere*dlon*deg2rad
265     & *abs( sin((lat+dlat)*deg2rad)-sin(lat*deg2rad) )
266     #ifdef USE_BACKWARD_COMPATIBLE_GRID
267     lat=yC(I,J,bi,bj)-delY( jGl(J,bj) )*0.5 _d 0
268     lon=yC(I,J,bi,bj)+delY( jGl(J,bj) )*0.5 _d 0
269 cnh 1.8 rA(I,J,bi,bj) = dyF(I,J,bi,bj)
270 adcroft 1.15 & *rSphere*(SIN(lon*deg2rad)-SIN(lat*deg2rad))
271     #endif /* USE_BACKWARD_COMPATIBLE_GRID */
272     ENDDO
273     ENDDO
274    
275     C-- Calculate vertical face area (u cells)
276     DO J=1-Oly,sNy+Oly
277     DO I=1-Olx+1,sNx+Olx ! NOTE range
278     C by averaging
279 adcroft 1.11 rAw(I,J,bi,bj) = 0.5*(rA(I,J,bi,bj)+rA(I-1,J,bi,bj))
280 adcroft 1.15 C by formula
281     c lat=yGloc(I,J)
282     c dlon=0.5*( delX( iGl(I,bi) ) + delX( iGl(I-1,bi) ) )
283     c dlat=delY( jGl(J,bj) )
284     c rAw(I,J,bi,bj) = rSphere*rSphere*dlon*deg2rad
285     c & *abs( sin((lat+dlat)*deg2rad)-sin(lat*deg2rad) )
286     ENDDO
287     ENDDO
288    
289     C-- Calculate vertical face area (v cells)
290     DO J=1-Oly,sNy+Oly
291     DO I=1-Olx,sNx+Olx
292     C by formula
293     lat=yC(I,J,bi,bj)
294     dlon=delX( iGl(I,bi) )
295     dlat=0.5*( delY( jGl(J,bj) ) + delY( jGl(J-1,bj) ) )
296     rAs(I,J,bi,bj) = rSphere*rSphere*dlon*deg2rad
297     & *abs( sin(lat*deg2rad)-sin((lat-dlat)*deg2rad) )
298     #ifdef USE_BACKWARD_COMPATIBLE_GRID
299     lon=yC(I,J,bi,bj)-delY( jGl(J,bj) )
300     lat=yC(I,J,bi,bj)
301     rAs(I,J,bi,bj) = rSphere*delX(iGl(I,bi))*deg2rad
302     & *rSphere*(SIN(lat*deg2rad)-SIN(lon*deg2rad))
303     #endif /* USE_BACKWARD_COMPATIBLE_GRID */
304     IF (abs(lat).GT.90..OR.abs(lat-dlat).GT.90.) rAs(I,J,bi,bj)=0.
305     ENDDO
306     ENDDO
307    
308     C-- Calculate vertical face area (vorticity points)
309     DO J=1-Oly,sNy+Oly
310     DO I=1-Olx,sNx+Olx
311     C by formula
312     lat=yC(I,J,bi,bj)
313     dlon=delX( iGl(I,bi) )
314     dlat=0.5*( delY( jGl(J,bj) ) + delY( jGl(J-1,bj) ) )
315     rAz(I,J,bi,bj) = rSphere*rSphere*dlon*deg2rad
316     & *abs( sin(lat*deg2rad)-sin((lat-dlat)*deg2rad) )
317     IF (abs(lat).GT.90..OR.abs(lat-dlat).GT.90.) rAz(I,J,bi,bj)=0.
318     ENDDO
319     ENDDO
320    
321     C-- Calculate trigonometric terms
322     DO J=1-Oly,sNy+Oly
323     DO I=1-Olx,sNx+Olx
324     lat=0.5*(yGloc(I,J)+yGloc(I,J+1))
325     tanPhiAtU(i,j,bi,bj)=tan(lat*deg2rad)
326     lat=0.5*(yGloc(I,J)+yGloc(I+1,J))
327     tanPhiAtV(i,j,bi,bj)=tan(lat*deg2rad)
328 adcroft 1.11 ENDDO
329 adcroft 1.18 ENDDO
330    
331     C-- Cosine(lat) scaling
332     DO J=1-OLy,sNy+OLy
333     jG = myYGlobalLo + (bj-1)*sNy + J-1
334     jG = min(max(1,jG),Ny)
335     IF (cosPower.NE.0.) THEN
336     cosFacU(J,bi,bj)=COS(yC(1,J,bi,bj)*deg2rad)
337     & **cosPower
338     cosFacV(J,bi,bj)=COS((yC(1,J,bi,bj)-0.5*delY(jG))*deg2rad)
339     & **cosPower
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 adcroft 1.11 ENDDO
349 adcroft 1.15
350     ENDDO ! bi
351     ENDDO ! bj
352    
353 cnh 1.1 RETURN
354     END

  ViewVC Help
Powered by ViewVC 1.1.22