/[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.3 - (show annotations) (download)
Fri Nov 4 01:19:24 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint57y_post, checkpoint58n_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58j_post, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58k_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.2: +1 -2 lines
remove unused variables (reduces number of compiler warning)

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_cylinder_grid.F,v 1.2 2005/07/31 22:07:48 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INI_CYLINDER_GRID
8 C !INTERFACE:
9 SUBROUTINE INI_CYLINDER_GRID( myThid )
10 C !DESCRIPTION: \bv
11 C /==========================================================\
12 C | SUBROUTINE INI_CYLINDER_GRID
13 C | o Initialise model coordinate system arrays |
14 C |==========================================================|
15 C | These arrays are used throughout the code in evaluating |
16 C | gradients, integrals and spatial avarages. This routine |
17 C | is called separately by each thread and initialise only |
18 C | the region of the domain it is "responsible" for. |
19 C | Under the spherical polar grid mode primitive distances |
20 C | in X is in degrees and Y in meters. |
21 C | Distance in Z are in m or Pa |
22 C | depending on the vertical gridding mode. |
23 C \==========================================================/
24 C \ev
25
26 C !USES:
27 IMPLICIT NONE
28 C === Global variables ===
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "GRID.h"
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C == Routine arguments ==
36 C myThid - Number of this instance of INI_CYLINDER
37 INTEGER myThid
38 CEndOfInterface
39
40 C !LOCAL VARIABLES:
41 C == Local variables ==
42 C xG, yG - Global coordinate location.
43 C xBase - South-west corner location for process.
44 C yBase
45 C zUpper - Work arrays for upper and lower
46 C zLower cell-face heights.
47 C phi - Temporary scalar
48 C iG, jG - Global coordinate index. Usually used to hold
49 C the south-west global coordinate of a tile.
50 C bi,bj - Loop counters
51 C zUpper - Temporary arrays holding z coordinates of
52 C zLower upper and lower faces.
53 C xBase - Lower coordinate for this threads cells
54 C yBase
55 C lat, latN, - Temporary variables used to hold latitude
56 C latS values.
57 C I,J,K
58 INTEGER iG, jG
59 INTEGER bi, bj
60 INTEGER I, J
61 _RL dtheta, thisRad, xG0, yG0
62
63 C "Long" real for temporary coordinate calculation
64 C NOTICE the extended range of indices!!
65 _RL xGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
66 _RL yGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
67
68 C The functions iGl, jGl return the "global" index with valid values beyond
69 C halo regions
70 C cnh wrote:
71 C > I dont understand why we would ever have to multiply the
72 C > overlap by the total domain size e.g
73 C > OLx*Nx, OLy*Ny.
74 C > Can anybody explain? Lines are in ini_spherical_polar_grid.F.
75 C > Surprised the code works if its wrong, so I am puzzled.
76 C jmc replied:
77 C Yes, I can explain this since I put this modification to work
78 C with small domain (where Oly > Ny, as for instance, zonal-average
79 C case):
80 C This has no effect on the acuracy of the evaluation of iGl(I,bi)
81 C and jGl(J,bj) since we take mod(a+OLx*Nx,Nx) and mod(b+OLy*Ny,Ny).
82 C But in case a or b is negative, then the FORTRAN function "mod"
83 C does not return the matematical value of the "modulus" function,
84 C and this is not good for your purpose.
85 C This is why I add +OLx*Nx and +OLy*Ny to be sure that the 1rst
86 C argument of the mod function is positive.
87 INTEGER iGl,jGl
88 iGl(I,bi) = 1+mod(myXGlobalLo-1+(bi-1)*sNx+I+Olx*Nx-1,Nx)
89 jGl(J,bj) = 1+mod(myYGlobalLo-1+(bj-1)*sNy+J+Oly*Ny-1,Ny)
90 CEOP
91
92
93 C For each tile ...
94 DO bj = myByLo(myThid), myByHi(myThid)
95 DO bi = myBxLo(myThid), myBxHi(myThid)
96
97 C-- "Global" index (place holder)
98 jG = myYGlobalLo + (bj-1)*sNy
99 iG = myXGlobalLo + (bi-1)*sNx
100
101 C-- First find coordinate of tile corner (meaning outer corner of halo)
102 xG0 = thetaMin
103 C Find the X-coordinate of the outer grid-line of the "real" tile
104 DO i=1, iG-1
105 xG0 = xG0 + delX(i)
106 ENDDO
107 C Back-step to the outer grid-line of the "halo" region
108 DO i=1, Olx
109 xG0 = xG0 - delX( 1+mod(Olx*Nx-1+iG-i,Nx) )
110 ENDDO
111 C Find the Y-coordinate of the outer grid-line of the "real" tile
112 yG0 = 0
113 DO j=1, jG-1
114 yG0 = yG0 + delY(j)
115 ENDDO
116 C Back-step to the outer grid-line of the "halo" region
117 DO j=1, Oly
118 yG0 = yG0 - delY( 1+mod(Oly*Ny-1+jG-j,Ny) )
119 ENDDO
120
121 C-- Calculate coordinates of cell corners for N+1 grid-lines
122 DO J=1-Oly,sNy+Oly +1
123 xGloc(1-Olx,J) = xG0
124 DO I=1-Olx,sNx+Olx
125 xGloc(I+1,J) = xGloc(I,J) + delX( iGl(I,bi) )
126 ENDDO
127 ENDDO
128 DO I=1-Olx,sNx+Olx +1
129 yGloc(I,1-Oly) = yG0
130 DO J=1-Oly,sNy+Oly
131 yGloc(I,J+1) = yGloc(I,J) + delY( jGl(J,bj) )
132 ENDDO
133 ENDDO
134
135 C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
136 DO J=1-Oly,sNy+Oly
137 DO I=1-Olx,sNx+Olx
138 xG(I,J,bi,bj) = xGloc(I,J)
139 yG(I,J,bi,bj) = yGloc(I,J)
140 ENDDO
141 ENDDO
142
143 C-- Calculate [xC,yC], coordinates of cell centers
144 DO J=1-Oly,sNy+Oly
145 DO I=1-Olx,sNx+Olx
146 C by averaging
147 xC(I,J,bi,bj) = 0.25*(
148 & xGloc(I,J)+xGloc(I+1,J)+xGloc(I,J+1)+xGloc(I+1,J+1) )
149 yC(I,J,bi,bj) = 0.25*(
150 & yGloc(I,J)+yGloc(I+1,J)+yGloc(I,J+1)+yGloc(I+1,J+1) )
151 ENDDO
152 ENDDO
153
154 C-- Calculate [dxF,dyF], lengths between cell faces (through center)
155 DO J=1-Oly,sNy+Oly
156 DO I=1-Olx,sNx+Olx
157 thisRad = yC(I,J,bi,bj)
158 dtheta = delX( iGl(I,bi) )
159 dXF(I,J,bi,bj) = thisRad*dtheta*deg2rad
160 dYF(I,J,bi,bj) = delY( jGl(J,bj) )
161 ENDDO
162 ENDDO
163
164 C-- Calculate [dxG,dyG], lengths along cell boundaries
165 DO J=1-Oly,sNy+Oly
166 DO I=1-Olx,sNx+Olx
167 thisRad = 0.5*(yGloc(I,J)+yGloc(I+1,J))
168 dtheta = delX( iGl(I,bi) )
169 dXG(I,J,bi,bj) = thisRad*dtheta*deg2rad
170 dYG(I,J,bi,bj) = delY( jGl(J,bj) )
171 ENDDO
172 ENDDO
173
174 C-- The following arrays are not defined in some parts of the halo
175 C region. We set them to zero here for safety. If they are ever
176 C referred to, especially in the denominator then it is a mistake!
177 DO J=1-Oly,sNy+Oly
178 DO I=1-Olx,sNx+Olx
179 dXC(I,J,bi,bj) = 0.
180 dYC(I,J,bi,bj) = 0.
181 dXV(I,J,bi,bj) = 0.
182 dYU(I,J,bi,bj) = 0.
183 rAw(I,J,bi,bj) = 0.
184 rAs(I,J,bi,bj) = 0.
185 ENDDO
186 ENDDO
187
188 C-- Calculate [dxC], zonal length between cell centers
189 DO J=1-Oly,sNy+Oly
190 DO I=1-Olx+1,sNx+Olx ! NOTE range
191 C by averaging
192 dXC(I,J,bi,bj) = 0.5D0*(dXF(I,J,bi,bj)+dXF(I-1,J,bi,bj))
193 ENDDO
194 ENDDO
195
196 C-- Calculate [dyC], meridional length between cell centers
197 DO J=1-Oly+1,sNy+Oly ! NOTE range
198 DO I=1-Olx,sNx+Olx
199 C by averaging
200 dYC(I,J,bi,bj) = 0.5*(dYF(I,J,bi,bj)+dYF(I,J-1,bi,bj))
201 ENDDO
202 ENDDO
203
204 C-- Calculate [dxV,dyU], length between velocity points (through corners)
205 DO J=1-Oly+1,sNy+Oly ! NOTE range
206 DO I=1-Olx+1,sNx+Olx ! NOTE range
207 C by averaging (method I)
208 dXV(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I-1,J,bi,bj))
209 dYU(I,J,bi,bj) = 0.5*(dYG(I,J,bi,bj)+dYG(I,J-1,bi,bj))
210 ENDDO
211 ENDDO
212
213
214
215 C-- Calculate vertical face area
216 DO J=1-Oly,sNy+Oly
217 DO I=1-Olx,sNx+Olx
218 C- All r(dr)(dtheta)
219 rA (I,J,bi,bj) = dxF(I,J,bi,bj)*dyF(I,J,bi,bj)
220 rAw(I,J,bi,bj) = dxC(I,J,bi,bj)*dyG(I,J,bi,bj)
221 rAs(I,J,bi,bj) = dxG(I,J,bi,bj)*dyC(I,J,bi,bj)
222 rAz(I,J,bi,bj) = dxV(I,J,bi,bj)*dyU(I,J,bi,bj)
223 C-- Set trigonometric terms & grid orientation:
224 tanPhiAtU(I,J,bi,bj) = 0.
225 tanPhiAtV(I,J,bi,bj) = 0.
226 angleCosC(I,J,bi,bj) = 1.
227 angleSinC(I,J,bi,bj) = 0.
228 ENDDO
229 ENDDO
230
231 C-- Cosine(lat) scaling
232 DO J=1-OLy,sNy+OLy
233 cosFacU(J,bi,bj)=1.
234 cosFacV(J,bi,bj)=1.
235 sqcosFacU(J,bi,bj)=1.
236 sqcosFacV(J,bi,bj)=1.
237 ENDDO
238
239 ENDDO ! bi
240 ENDDO ! bj
241
242 C-- Set default (=whole domain) for where relaxation to climatology applies
243 IF ( latBandClimRelax.EQ.UNSET_RL ) THEN
244 _BEGIN_MASTER(myThid)
245 latBandClimRelax = 0.
246 DO j=1,Ny
247 latBandClimRelax = latBandClimRelax + delY(j)
248 ENDDO
249 latBandClimRelax = latBandClimRelax*3. _d 0
250 _END_MASTER(myThid)
251 ENDIF
252
253 RETURN
254 END

  ViewVC Help
Powered by ViewVC 1.1.22