/[MITgcm]/MITgcm_contrib/osse/codemod/ini_cylinder.F
ViewVC logotype

Annotation of /MITgcm_contrib/osse/codemod/ini_cylinder.F

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


Revision 1.1 - (hide annotations) (download)
Tue Jun 22 19:44:40 2004 UTC (21 years, 1 month ago) by afe
Branch: MAIN
CVS Tags: HEAD
attempts to get tank config working with current checkpoint

1 afe 1.1 C $Header: /u/gcmpack/MITgcm_contrib/osse/code/ini_cylinder.F,v 1.1 2004/04/26 14:08:04 afe Exp $
2     C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     #undef USE_BACKWARD_COMPATIBLE_GRID
7    
8     CBOP
9     C !ROUTINE: INI_CYLINDER
10     C !INTERFACE:
11     SUBROUTINE INI_CYLINDER( myThid )
12     C !DESCRIPTION: \bv
13     C /==========================================================\
14     C | SUBROUTINE INI_CYLINDER
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    
36     C !INPUT/OUTPUT PARAMETERS:
37     C == Routine arguments ==
38     C myThid - Number of this instance of INI_CYLINDER
39     INTEGER myThid
40     CEndOfInterface
41    
42     C !LOCAL VARIABLES:
43     C == Local variables ==
44     C xG, yG - Global coordinate location.
45     C xBase - South-west corner location for process.
46     C yBase
47     C zUpper - Work arrays for upper and lower
48     C zLower cell-face heights.
49     C phi - Temporary scalar
50     C iG, jG - Global coordinate index. Usually used to hold
51     C the south-west global coordinate of a tile.
52     C bi,bj - Loop counters
53     C zUpper - Temporary arrays holding z coordinates of
54     C zLower upper and lower faces.
55     C xBase - Lower coordinate for this threads cells
56     C yBase
57     C lat, latN, - Temporary variables used to hold latitude
58     C latS values.
59     C I,J,K
60     INTEGER iG, jG
61     INTEGER bi, bj
62     INTEGER I, J
63     _RL dtheta, thisRad, xG0, yG0
64     CHARACTER*(MAX_LEN_MBUF) msgBuf
65    
66     C "Long" real for temporary coordinate calculation
67     C NOTICE the extended range of indices!!
68     _RL xGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
69     _RL yGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
70    
71     C The functions iGl, jGl return the "global" index with valid values beyond
72     C halo regions
73     C cnh wrote:
74     C > I dont understand why we would ever have to multiply the
75     C > overlap by the total domain size e.g
76     C > OLx*Nx, OLy*Ny.
77     C > Can anybody explain? Lines are in ini_spherical_polar_grid.F.
78     C > Surprised the code works if its wrong, so I am puzzled.
79     C jmc replied:
80     C Yes, I can explain this since I put this modification to work
81     C with small domain (where Oly > Ny, as for instance, zonal-average
82     C case):
83     C This has no effect on the acuracy of the evaluation of iGl(I,bi)
84     C and jGl(J,bj) since we take mod(a+OLx*Nx,Nx) and mod(b+OLy*Ny,Ny).
85     C But in case a or b is negative, then the FORTRAN function "mod"
86     C does not return the matematical value of the "modulus" function,
87     C and this is not good for your purpose.
88     C This is why I add +OLx*Nx and +OLy*Ny to be sure that the 1rst
89     C argument of the mod function is positive.
90     INTEGER iGl,jGl
91     iGl(I,bi) = 1+mod(myXGlobalLo-1+(bi-1)*sNx+I+Olx*Nx-1,Nx)
92     jGl(J,bj) = 1+mod(myYGlobalLo-1+(bj-1)*sNy+J+Oly*Ny-1,Ny)
93     CEOP
94    
95    
96     C For each tile ...
97     DO bj = myByLo(myThid), myByHi(myThid)
98     DO bi = myBxLo(myThid), myBxHi(myThid)
99    
100     C-- "Global" index (place holder)
101     jG = myYGlobalLo + (bj-1)*sNy
102     iG = myXGlobalLo + (bi-1)*sNx
103    
104     C-- First find coordinate of tile corner (meaning outer corner of halo)
105     xG0 = thetaMin
106     C Find the X-coordinate of the outer grid-line of the "real" tile
107     DO i=1, iG-1
108     xG0 = xG0 + delX(i)
109     ENDDO
110     C Back-step to the outer grid-line of the "halo" region
111     DO i=1, Olx
112     xG0 = xG0 - delX( 1+mod(Olx*Nx-1+iG-i,Nx) )
113     ENDDO
114     C Find the Y-coordinate of the outer grid-line of the "real" tile
115     yG0 = 0
116     DO j=1, jG-1
117     yG0 = yG0 + delY(j)
118     ENDDO
119     C Back-step to the outer grid-line of the "halo" region
120     DO j=1, Oly
121     yG0 = yG0 - delY( 1+mod(Oly*Ny-1+jG-j,Ny) )
122     ENDDO
123    
124     C-- Calculate coordinates of cell corners for N+1 grid-lines
125     DO J=1-Oly,sNy+Oly +1
126     xGloc(1-Olx,J) = xG0
127     DO I=1-Olx,sNx+Olx
128     xGloc(I+1,J) = xGloc(I,J) + delX( iGl(I,bi) )
129     ENDDO
130     ENDDO
131     DO I=1-Olx,sNx+Olx +1
132     yGloc(I,1-Oly) = yG0
133     DO J=1-Oly,sNy+Oly
134     yGloc(I,J+1) = yGloc(I,J) + delY( jGl(J,bj) )
135     ENDDO
136     ENDDO
137    
138     C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
139     DO J=1-Oly,sNy+Oly
140     DO I=1-Olx,sNx+Olx
141     xG(I,J,bi,bj) = xGloc(I,J)
142     yG(I,J,bi,bj) = yGloc(I,J)
143     ENDDO
144     ENDDO
145    
146     C-- Calculate [xC,yC], coordinates of cell centers
147     DO J=1-Oly,sNy+Oly
148     DO I=1-Olx,sNx+Olx
149     C by averaging
150     xC(I,J,bi,bj) = 0.25*(
151     & xGloc(I,J)+xGloc(I+1,J)+xGloc(I,J+1)+xGloc(I+1,J+1) )
152     yC(I,J,bi,bj) = 0.25*(
153     & yGloc(I,J)+yGloc(I+1,J)+yGloc(I,J+1)+yGloc(I+1,J+1) )
154     ENDDO
155     ENDDO
156    
157     C-- Calculate [dxF,dyF], lengths between cell faces (through center)
158     DO J=1-Oly,sNy+Oly
159     DO I=1-Olx,sNx+Olx
160     thisRad = yC(I,J,bi,bj)
161     dtheta = delX( iGl(I,bi) )
162     dXF(I,J,bi,bj) = thisRad*dtheta*deg2rad
163     dYF(I,J,bi,bj) = delY( jGl(J,bj) )
164     ENDDO
165     ENDDO
166    
167     C-- Calculate [dxG,dyG], lengths along cell boundaries
168     DO J=1-Oly,sNy+Oly
169     DO I=1-Olx,sNx+Olx
170     thisRad = 0.5*(yGloc(I,J)+yGloc(I+1,J))
171     dtheta = delX( iGl(I,bi) )
172     dXG(I,J,bi,bj) = thisRad*dtheta*deg2rad
173     dYG(I,J,bi,bj) = delY( jGl(J,bj) )
174     ENDDO
175     ENDDO
176    
177     C-- The following arrays are not defined in some parts of the halo
178     C region. We set them to zero here for safety. If they are ever
179     C referred to, especially in the denominator then it is a mistake!
180     DO J=1-Oly,sNy+Oly
181     DO I=1-Olx,sNx+Olx
182     dXC(I,J,bi,bj) = 0.
183     dYC(I,J,bi,bj) = 0.
184     dXV(I,J,bi,bj) = 0.
185     dYU(I,J,bi,bj) = 0.
186     rAw(I,J,bi,bj) = 0.
187     rAs(I,J,bi,bj) = 0.
188     ENDDO
189     ENDDO
190    
191     C-- Calculate [dxC], zonal length between cell centers
192     DO J=1-Oly,sNy+Oly
193     DO I=1-Olx+1,sNx+Olx ! NOTE range
194     C by averaging
195     dXC(I,J,bi,bj) = 0.5D0*(dXF(I,J,bi,bj)+dXF(I-1,J,bi,bj))
196     ENDDO
197     ENDDO
198    
199     C-- Calculate [dyC], meridional length between cell centers
200     DO J=1-Oly+1,sNy+Oly ! NOTE range
201     DO I=1-Olx,sNx+Olx
202     C by averaging
203     dYC(I,J,bi,bj) = 0.5*(dYF(I,J,bi,bj)+dYF(I,J-1,bi,bj))
204     ENDDO
205     ENDDO
206    
207     C-- Calculate [dxV,dyU], length between velocity points (through corners)
208     DO J=1-Oly+1,sNy+Oly ! NOTE range
209     DO I=1-Olx+1,sNx+Olx ! NOTE range
210     C by averaging (method I)
211     dXV(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I-1,J,bi,bj))
212     dYU(I,J,bi,bj) = 0.5*(dYG(I,J,bi,bj)+dYG(I,J-1,bi,bj))
213     ENDDO
214     ENDDO
215    
216    
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     tanPhiAtU(I,J,bi,bj) = 0.
227     tanPhiAtV(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     RETURN
243     END

  ViewVC Help
Powered by ViewVC 1.1.22