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

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

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


Revision 1.6 - (show annotations) (download)
Sat Apr 17 18:25:12 2010 UTC (14 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.5: +104 -101 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_cylinder_grid.F,v 1.5 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 CBOP
8 C !ROUTINE: INI_CYLINDER_GRID
9 C !INTERFACE:
10 SUBROUTINE INI_CYLINDER_GRID( myThid )
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE INI_CYLINDER_GRID
15 C | o Initialise model coordinate system arrays
16 C *==========================================================*
17 C | These arrays are used throughout the code in evaluating
18 C | gradients, integrals and spatial avarages. This routine
19 C | is called separately by each thread and initialise only
20 C | the region of the domain it is "responsible" for.
21 C | Under the spherical polar grid mode primitive distances
22 C | in X is in degrees and Y in meters.
23 C | 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 c#ifdef ALLOW_EXCH2
36 c#include "W2_EXCH2_SIZE.h"
37 c#include "W2_EXCH2_TOPOLOGY.h"
38 c#include "W2_EXCH2_PARAMS.h"
39 c#endif /* ALLOW_EXCH2 */
40
41 C !INPUT/OUTPUT PARAMETERS:
42 C == Routine arguments ==
43 C myThid :: my Thread Id number
44 INTEGER myThid
45
46 C !LOCAL VARIABLES:
47 C == Local variables ==
48 C xG0,yG0 :: coordinate of South-West tile-corner
49 C iG, jG :: Global coordinate index. Usually used to hold
50 C :: the south-west global coordinate of a tile.
51 C bi,bj :: tile indices
52 C i, j :: loop counters
53 INTEGER iG, jG
54 INTEGER bi, bj
55 INTEGER i, j
56 _RL dtheta, thisRad, xG0, yG0
57
58 C "Long" real for temporary coordinate calculation
59 C NOTICE the extended range of indices!!
60 _RL xGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
61 _RL yGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
62
63 C The functions iGl, jGl return the "global" index with valid values beyond
64 C halo regions
65 C cnh wrote:
66 C > I dont understand why we would ever have to multiply the
67 C > overlap by the total domain size e.g
68 C > OLx*Nx, OLy*Ny.
69 C > Can anybody explain? Lines are in ini_spherical_polar_grid.F.
70 C > Surprised the code works if its wrong, so I am puzzled.
71 C jmc replied:
72 C Yes, I can explain this since I put this modification to work
73 C with small domain (where Oly > Ny, as for instance, zonal-average
74 C case):
75 C This has no effect on the acuracy of the evaluation of iGl(I,bi)
76 C and jGl(j,bj) since we take mod(a+OLx*Nx,Nx) and mod(b+OLy*Ny,Ny).
77 C But in case a or b is negative, then the FORTRAN function "mod"
78 C does not return the matematical value of the "modulus" function,
79 C and this is not good for your purpose.
80 C This is why I add +OLx*Nx and +OLy*Ny to be sure that the 1rst
81 C argument of the mod function is positive.
82 INTEGER iGl,jGl
83 iGl(i,bi) = 1+MOD(myXGlobalLo-1+(bi-1)*sNx+i+Olx*Nx-1,Nx)
84 jGl(j,bj) = 1+MOD(myYGlobalLo-1+(bj-1)*sNy+j+Oly*Ny-1,Ny)
85 c#ifdef ALLOW_EXCH2
86 c INTEGER tN
87 c#endif /* ALLOW_EXCH2 */
88 CEOP
89
90 C For each tile ...
91 DO bj = myByLo(myThid), myByHi(myThid)
92 DO bi = myBxLo(myThid), myBxHi(myThid)
93
94 C-- "Global" index (place holder)
95 jG = myYGlobalLo + (bj-1)*sNy
96 iG = myXGlobalLo + (bi-1)*sNx
97 c#ifdef ALLOW_EXCH2
98 c IF ( W2_useE2ioLayOut ) THEN
99 cC- note: does not work for non-uniform delX or delY
100 c tN = W2_myTileList(bi,bj)
101 c iG = exch2_txGlobalo(tN)
102 c jG = exch2_tyGlobalo(tN)
103 c ENDIF
104 c#endif /* ALLOW_EXCH2 */
105
106 C-- First find coordinate of tile corner (meaning outer corner of halo)
107 xG0 = xgOrigin
108 C Find the X-coordinate of the outer grid-line of the "real" tile
109 DO i=1, iG-1
110 xG0 = xG0 + delX(i)
111 ENDDO
112 C Back-step to the outer grid-line of the "halo" region
113 DO i=1, Olx
114 xG0 = xG0 - delX( 1+mod(Olx*Nx-1+iG-i,Nx) )
115 ENDDO
116 C Find the Y-coordinate of the outer grid-line of the "real" tile
117 yG0 = ygOrigin
118 DO j=1, jG-1
119 yG0 = yG0 + delY(j)
120 ENDDO
121 C Back-step to the outer grid-line of the "halo" region
122 DO j=1, Oly
123 yG0 = yG0 - delY( 1+mod(Oly*Ny-1+jG-j,Ny) )
124 ENDDO
125
126 C-- Calculate coordinates of cell corners for N+1 grid-lines
127 DO j=1-Oly,sNy+Oly +1
128 xGloc(1-Olx,j) = xG0
129 DO i=1-Olx,sNx+Olx
130 xGloc(i+1,j) = xGloc(i,j) + delX( iGl(i,bi) )
131 ENDDO
132 ENDDO
133 DO i=1-Olx,sNx+Olx +1
134 yGloc(i,1-Oly) = yG0
135 DO j=1-Oly,sNy+Oly
136 yGloc(i,j+1) = yGloc(i,j) + delY( jGl(j,bj) )
137 ENDDO
138 ENDDO
139
140 C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
141 DO j=1-Oly,sNy+Oly
142 DO i=1-Olx,sNx+Olx
143 xG(i,j,bi,bj) = xGloc(i,j)
144 yG(i,j,bi,bj) = yGloc(i,j)
145 ENDDO
146 ENDDO
147
148 C-- Calculate [xC,yC], coordinates of cell centers
149 DO j=1-Oly,sNy+Oly
150 DO i=1-Olx,sNx+Olx
151 C by averaging
152 xC(i,j,bi,bj) = 0.25 _d 0*(
153 & xGloc(i,j)+xGloc(i+1,j)+xGloc(i,j+1)+xGloc(i+1,j+1) )
154 yC(i,j,bi,bj) = 0.25 _d 0*(
155 & yGloc(i,j)+yGloc(i+1,j)+yGloc(i,j+1)+yGloc(i+1,j+1) )
156 ENDDO
157 ENDDO
158
159 C-- Calculate [dxF,dyF], lengths between cell faces (through center)
160 DO j=1-Oly,sNy+Oly
161 DO i=1-Olx,sNx+Olx
162 thisRad = yC(i,j,bi,bj)
163 dtheta = delX( iGl(i,bi) )
164 dxF(i,j,bi,bj) = thisRad*dtheta*deg2rad
165 dyF(i,j,bi,bj) = delY( jGl(j,bj) )
166 ENDDO
167 ENDDO
168
169 C-- Calculate [dxG,dyG], lengths along cell boundaries
170 DO j=1-Oly,sNy+Oly
171 DO i=1-Olx,sNx+Olx
172 thisRad = 0.5 _d 0*(yGloc(i,j)+yGloc(i+1,j))
173 dtheta = delX( iGl(i,bi) )
174 dxG(i,j,bi,bj) = thisRad*dtheta*deg2rad
175 dyG(i,j,bi,bj) = delY( jGl(j,bj) )
176 ENDDO
177 ENDDO
178
179 C-- The following arrays are not defined in some parts of the halo
180 C region. We set them to zero here for safety. If they are ever
181 C referred to, especially in the denominator then it is a mistake!
182 DO j=1-Oly,sNy+Oly
183 DO i=1-Olx,sNx+Olx
184 dxC(i,j,bi,bj) = 0.
185 dyC(i,j,bi,bj) = 0.
186 dxV(i,j,bi,bj) = 0.
187 dyU(i,j,bi,bj) = 0.
188 rAw(i,j,bi,bj) = 0.
189 rAs(i,j,bi,bj) = 0.
190 ENDDO
191 ENDDO
192
193 C-- Calculate [dxC], zonal length between cell centers
194 DO j=1-Oly,sNy+Oly
195 DO i=1-Olx+1,sNx+Olx ! NOTE range
196 C by averaging
197 dxC(i,j,bi,bj) = 0.5 _d 0*(dxF(i,j,bi,bj)+dxF(i-1,j,bi,bj))
198 ENDDO
199 ENDDO
200
201 C-- Calculate [dyC], meridional length between cell centers
202 DO j=1-Oly+1,sNy+Oly ! NOTE range
203 DO i=1-Olx,sNx+Olx
204 C by averaging
205 dyC(i,j,bi,bj) = 0.5 _d 0*(dyF(i,j,bi,bj)+dyF(i,j-1,bi,bj))
206 ENDDO
207 ENDDO
208
209 C-- Calculate [dxV,dyU], length between velocity points (through corners)
210 DO j=1-Oly+1,sNy+Oly ! NOTE range
211 DO i=1-Olx+1,sNx+Olx ! NOTE range
212 C by averaging (method I)
213 dxV(i,j,bi,bj) = 0.5 _d 0*(dxG(i,j,bi,bj)+dxG(i-1,j,bi,bj))
214 dyU(i,j,bi,bj) = 0.5 _d 0*(dyG(i,j,bi,bj)+dyG(i,j-1,bi,bj))
215 ENDDO
216 ENDDO
217
218 C-- Calculate vertical face area
219 DO j=1-Oly,sNy+Oly
220 DO i=1-Olx,sNx+Olx
221 C- All r(dr)(dtheta)
222 rA (i,j,bi,bj) = dxF(i,j,bi,bj)*dyF(i,j,bi,bj)
223 rAw(i,j,bi,bj) = dxC(i,j,bi,bj)*dyG(i,j,bi,bj)
224 rAs(i,j,bi,bj) = dxG(i,j,bi,bj)*dyC(i,j,bi,bj)
225 rAz(i,j,bi,bj) = dxV(i,j,bi,bj)*dyU(i,j,bi,bj)
226 C-- Set trigonometric terms & grid orientation:
227 tanPhiAtU(i,j,bi,bj) = 0.
228 tanPhiAtV(i,j,bi,bj) = 0.
229 angleCosC(i,j,bi,bj) = 1.
230 angleSinC(i,j,bi,bj) = 0.
231 ENDDO
232 ENDDO
233
234 C-- Cosine(lat) scaling
235 DO j=1-OLy,sNy+OLy
236 cosFacU(j,bi,bj)=1.
237 cosFacV(j,bi,bj)=1.
238 sqcosFacU(j,bi,bj)=1.
239 sqcosFacV(j,bi,bj)=1.
240 ENDDO
241
242 ENDDO ! bi
243 ENDDO ! bj
244
245 C-- Set default (=whole domain) for where relaxation to climatology applies
246 IF ( latBandClimRelax.EQ.UNSET_RL ) THEN
247 _BEGIN_MASTER(myThid)
248 latBandClimRelax = 0.
249 DO j=1,Ny
250 latBandClimRelax = latBandClimRelax + delY(j)
251 ENDDO
252 latBandClimRelax = latBandClimRelax*3. _d 0
253 _END_MASTER(myThid)
254 ENDIF
255
256 RETURN
257 END

  ViewVC Help
Powered by ViewVC 1.1.22