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

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

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


Revision 1.1 - (hide annotations) (download)
Wed Jul 13 00:34:39 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57o_post, checkpoint57m_post, checkpoint57n_post, checkpoint57l_post
ini_cylinder.F renamed ini_cylinder_grid.F (like the other grids).

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/model/src/ini_cylinder.F,v 1.1 2004/06/24 20:25:44 afe 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     CHARACTER*(MAX_LEN_MBUF) msgBuf
63    
64     C "Long" real for temporary coordinate calculation
65     C NOTICE the extended range of indices!!
66     _RL xGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
67     _RL yGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
68    
69     C The functions iGl, jGl return the "global" index with valid values beyond
70     C halo regions
71     C cnh wrote:
72     C > I dont understand why we would ever have to multiply the
73     C > overlap by the total domain size e.g
74     C > OLx*Nx, OLy*Ny.
75     C > Can anybody explain? Lines are in ini_spherical_polar_grid.F.
76     C > Surprised the code works if its wrong, so I am puzzled.
77     C jmc replied:
78     C Yes, I can explain this since I put this modification to work
79     C with small domain (where Oly > Ny, as for instance, zonal-average
80     C case):
81     C This has no effect on the acuracy of the evaluation of iGl(I,bi)
82     C and jGl(J,bj) since we take mod(a+OLx*Nx,Nx) and mod(b+OLy*Ny,Ny).
83     C But in case a or b is negative, then the FORTRAN function "mod"
84     C does not return the matematical value of the "modulus" function,
85     C and this is not good for your purpose.
86     C This is why I add +OLx*Nx and +OLy*Ny to be sure that the 1rst
87     C argument of the mod function is positive.
88     INTEGER iGl,jGl
89     iGl(I,bi) = 1+mod(myXGlobalLo-1+(bi-1)*sNx+I+Olx*Nx-1,Nx)
90     jGl(J,bj) = 1+mod(myYGlobalLo-1+(bj-1)*sNy+J+Oly*Ny-1,Ny)
91     CEOP
92    
93    
94     C For each tile ...
95     DO bj = myByLo(myThid), myByHi(myThid)
96     DO bi = myBxLo(myThid), myBxHi(myThid)
97    
98     C-- "Global" index (place holder)
99     jG = myYGlobalLo + (bj-1)*sNy
100     iG = myXGlobalLo + (bi-1)*sNx
101    
102     C-- First find coordinate of tile corner (meaning outer corner of halo)
103     xG0 = thetaMin
104     C Find the X-coordinate of the outer grid-line of the "real" tile
105     DO i=1, iG-1
106     xG0 = xG0 + delX(i)
107     ENDDO
108     C Back-step to the outer grid-line of the "halo" region
109     DO i=1, Olx
110     xG0 = xG0 - delX( 1+mod(Olx*Nx-1+iG-i,Nx) )
111     ENDDO
112     C Find the Y-coordinate of the outer grid-line of the "real" tile
113     yG0 = 0
114     DO j=1, jG-1
115     yG0 = yG0 + delY(j)
116     ENDDO
117     C Back-step to the outer grid-line of the "halo" region
118     DO j=1, Oly
119     yG0 = yG0 - delY( 1+mod(Oly*Ny-1+jG-j,Ny) )
120     ENDDO
121    
122     C-- Calculate coordinates of cell corners for N+1 grid-lines
123     DO J=1-Oly,sNy+Oly +1
124     xGloc(1-Olx,J) = xG0
125     DO I=1-Olx,sNx+Olx
126     xGloc(I+1,J) = xGloc(I,J) + delX( iGl(I,bi) )
127     ENDDO
128     ENDDO
129     DO I=1-Olx,sNx+Olx +1
130     yGloc(I,1-Oly) = yG0
131     DO J=1-Oly,sNy+Oly
132     yGloc(I,J+1) = yGloc(I,J) + delY( jGl(J,bj) )
133     ENDDO
134     ENDDO
135    
136     C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
137     DO J=1-Oly,sNy+Oly
138     DO I=1-Olx,sNx+Olx
139     xG(I,J,bi,bj) = xGloc(I,J)
140     yG(I,J,bi,bj) = yGloc(I,J)
141     ENDDO
142     ENDDO
143    
144     C-- Calculate [xC,yC], coordinates of cell centers
145     DO J=1-Oly,sNy+Oly
146     DO I=1-Olx,sNx+Olx
147     C by averaging
148     xC(I,J,bi,bj) = 0.25*(
149     & xGloc(I,J)+xGloc(I+1,J)+xGloc(I,J+1)+xGloc(I+1,J+1) )
150     yC(I,J,bi,bj) = 0.25*(
151     & yGloc(I,J)+yGloc(I+1,J)+yGloc(I,J+1)+yGloc(I+1,J+1) )
152     ENDDO
153     ENDDO
154    
155     C-- Calculate [dxF,dyF], lengths between cell faces (through center)
156     DO J=1-Oly,sNy+Oly
157     DO I=1-Olx,sNx+Olx
158     thisRad = yC(I,J,bi,bj)
159     dtheta = delX( iGl(I,bi) )
160     dXF(I,J,bi,bj) = thisRad*dtheta*deg2rad
161     dYF(I,J,bi,bj) = delY( jGl(J,bj) )
162     ENDDO
163     ENDDO
164    
165     C-- Calculate [dxG,dyG], lengths along cell boundaries
166     DO J=1-Oly,sNy+Oly
167     DO I=1-Olx,sNx+Olx
168     thisRad = 0.5*(yGloc(I,J)+yGloc(I+1,J))
169     dtheta = delX( iGl(I,bi) )
170     dXG(I,J,bi,bj) = thisRad*dtheta*deg2rad
171     dYG(I,J,bi,bj) = delY( jGl(J,bj) )
172     ENDDO
173     ENDDO
174    
175     C-- The following arrays are not defined in some parts of the halo
176     C region. We set them to zero here for safety. If they are ever
177     C referred to, especially in the denominator then it is a mistake!
178     DO J=1-Oly,sNy+Oly
179     DO I=1-Olx,sNx+Olx
180     dXC(I,J,bi,bj) = 0.
181     dYC(I,J,bi,bj) = 0.
182     dXV(I,J,bi,bj) = 0.
183     dYU(I,J,bi,bj) = 0.
184     rAw(I,J,bi,bj) = 0.
185     rAs(I,J,bi,bj) = 0.
186     ENDDO
187     ENDDO
188    
189     C-- Calculate [dxC], zonal length between cell centers
190     DO J=1-Oly,sNy+Oly
191     DO I=1-Olx+1,sNx+Olx ! NOTE range
192     C by averaging
193     dXC(I,J,bi,bj) = 0.5D0*(dXF(I,J,bi,bj)+dXF(I-1,J,bi,bj))
194     ENDDO
195     ENDDO
196    
197     C-- Calculate [dyC], meridional length between cell centers
198     DO J=1-Oly+1,sNy+Oly ! NOTE range
199     DO I=1-Olx,sNx+Olx
200     C by averaging
201     dYC(I,J,bi,bj) = 0.5*(dYF(I,J,bi,bj)+dYF(I,J-1,bi,bj))
202     ENDDO
203     ENDDO
204    
205     C-- Calculate [dxV,dyU], length between velocity points (through corners)
206     DO J=1-Oly+1,sNy+Oly ! NOTE range
207     DO I=1-Olx+1,sNx+Olx ! NOTE range
208     C by averaging (method I)
209     dXV(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I-1,J,bi,bj))
210     dYU(I,J,bi,bj) = 0.5*(dYG(I,J,bi,bj)+dYG(I,J-1,bi,bj))
211     ENDDO
212     ENDDO
213    
214    
215    
216     C-- Calculate vertical face area
217     DO J=1-Oly,sNy+Oly
218     DO I=1-Olx,sNx+Olx
219     C- All r(dr)(dtheta)
220     rA (I,J,bi,bj) = dxF(I,J,bi,bj)*dyF(I,J,bi,bj)
221     rAw(I,J,bi,bj) = dxC(I,J,bi,bj)*dyG(I,J,bi,bj)
222     rAs(I,J,bi,bj) = dxG(I,J,bi,bj)*dyC(I,J,bi,bj)
223     rAz(I,J,bi,bj) = dxV(I,J,bi,bj)*dyU(I,J,bi,bj)
224     C-- Set trigonometric terms & grid orientation:
225     tanPhiAtU(I,J,bi,bj) = 0.
226     tanPhiAtV(I,J,bi,bj) = 0.
227     angleCosC(I,J,bi,bj) = 1.
228     angleSinC(I,J,bi,bj) = 0.
229     ENDDO
230     ENDDO
231    
232     C-- Cosine(lat) scaling
233     DO J=1-OLy,sNy+OLy
234     cosFacU(J,bi,bj)=1.
235     cosFacV(J,bi,bj)=1.
236     sqcosFacU(J,bi,bj)=1.
237     sqcosFacV(J,bi,bj)=1.
238     ENDDO
239    
240     ENDDO ! bi
241     ENDDO ! bj
242    
243     RETURN
244     END

  ViewVC Help
Powered by ViewVC 1.1.22