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

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

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


Revision 1.12 - (show annotations) (download)
Wed Dec 9 16:11:52 1998 UTC (25 years, 5 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint19
Changes since 1.11: +2 -1 lines
Added IMPLICIT NONE in a lot of subroutines.
Also corrected the recip_Rhonil bug: we didn't set it in ini_parms.F

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_spherical_polar_grid.F,v 1.11 1998/11/30 23:45:25 adcroft Exp $
2
3 #include "CPP_OPTIONS.h"
4
5 CStartOfInterface
6 SUBROUTINE INI_SPHERICAL_POLAR_GRID( myThid )
7 C /==========================================================\
8 C | SUBROUTINE INI_SPHERICAL_POLAR_GRID |
9 C | o Initialise model coordinate system |
10 C |==========================================================|
11 C | These arrays are used throughout the code in evaluating |
12 C | gradients, integrals and spatial avarages. This routine |
13 C | is called separately by each thread and initialise only |
14 C | the region of the domain it is "responsible" for. |
15 C | Notes: |
16 C | Two examples are included. One illustrates the |
17 C | initialisation of a cartesian grid. The other shows the |
18 C | inialisation of a spherical polar grid. Other orthonormal|
19 C | grids can be fitted into this design. In this case |
20 C | custom metric terms also need adding to account for the |
21 C | projections of velocity vectors onto these grids. |
22 C | The structure used here also makes it possible to |
23 C | implement less regular grid mappings. In particular |
24 C | o Schemes which leave out blocks of the domain that are |
25 C | all land could be supported. |
26 C | o Multi-level schemes such as icosohedral or cubic |
27 C | grid projections onto a sphere can also be fitted |
28 C | within the strategy we use. |
29 C | Both of the above also require modifying the support |
30 C | routines that map computational blocks to simulation |
31 C | domain blocks. |
32 C | Under the spherical polar grid mode primitive distances |
33 C | in X and Y are in degrees. Distance in Z are in m or Pa |
34 C | depending on the vertical gridding mode. |
35 C \==========================================================/
36 IMPLICIT NONE
37
38 C === Global variables ===
39 #include "SIZE.h"
40 #include "EEPARAMS.h"
41 #include "PARAMS.h"
42 #include "GRID.h"
43
44 C == Routine arguments ==
45 C myThid - Number of this instance of INI_CARTESIAN_GRID
46 INTEGER myThid
47 CEndOfInterface
48
49 C == Local variables ==
50 C xG, yG - Global coordinate location.
51 C zG
52 C xBase - South-west corner location for process.
53 C yBase
54 C zUpper - Work arrays for upper and lower
55 C zLower cell-face heights.
56 C phi - Temporary scalar
57 C iG, jG - Global coordinate index. Usually used to hold
58 C the south-west global coordinate of a tile.
59 C bi,bj - Loop counters
60 C zUpper - Temporary arrays holding z coordinates of
61 C zLower upper and lower faces.
62 C xBase - Lower coordinate for this threads cells
63 C yBase
64 C lat, latN, - Temporary variables used to hold latitude
65 C latS values.
66 C I,J,K
67 _RL xG, yG, zG
68 _RL phi
69 _RL zUpper(Nr), zLower(Nr)
70 _RL xBase, yBase
71 INTEGER iG, jG
72 INTEGER bi, bj
73 INTEGER I, J, K
74 _RL lat, latS, latN
75
76 C-- Example of inialisation for spherical polar grid
77 C-- First set coordinates of cell centers
78 C This operation is only performed at start up so for more
79 C complex configurations it is usually OK to pass iG, jG to a custom
80 C function and have it return xG and yG.
81 C Set up my local grid first
82 C Note: In the spherical polar case delX and delY are given in
83 C degrees and are relative to some starting latitude and
84 C longitude - phiMin and thetaMin.
85 xC0 = thetaMin
86 yC0 = phiMin
87 DO bj = myByLo(myThid), myByHi(myThid)
88 jG = myYGlobalLo + (bj-1)*sNy
89 DO bi = myBxLo(myThid), myBxHi(myThid)
90 iG = myXGlobalLo + (bi-1)*sNx
91 yBase = phiMin
92 xBase = thetaMin
93 DO i=1,iG-1
94 xBase = xBase + delX(i)
95 ENDDO
96 DO j=1,jG-1
97 yBase = yBase + delY(j)
98 ENDDO
99 yG = yBase
100 DO J=1,sNy
101 xG = xBase
102 DO I=1,sNx
103 xc(I,J,bi,bj) = xG + delX(iG+i-1)*0.5 _d 0
104 yc(I,J,bi,bj) = yG + delY(jG+j-1)*0.5 _d 0
105 xG = xG + delX(iG+I-1)
106 dxF(I,J,bi,bj) = delX(iG+i-1)*deg2rad
107 & *rSphere*COS(yc(I,J,bi,bj)*deg2rad)
108 dyF(I,J,bi,bj) = delY(jG+j-1)*deg2rad*rSphere
109 ENDDO
110 yG = yG + delY(jG+J-1)
111 ENDDO
112 ENDDO
113 ENDDO
114 C Now sync. and get edge regions from other threads and/or processes.
115 C Note: We could just set the overlap regions ourselves here but
116 C exchanging edges is safer and is good practice!
117 _EXCH_XY_R4( xc, myThid )
118 _EXCH_XY_R4( yc, myThid )
119 _EXCH_XY_R4(dxF, myThid )
120 _EXCH_XY_R4(dyF, myThid )
121
122 C-- Calculate separation between other points
123 C dxG, dyG are separations between cell corners along cell faces.
124 DO bj = myByLo(myThid), myByHi(myThid)
125 DO bi = myBxLo(myThid), myBxHi(myThid)
126 DO J=1,sNy
127 DO I=1,sNx
128 jG = myYGlobalLo + (bj-1)*sNy + J-1
129 iG = myXGlobalLo + (bi-1)*sNx + I-1
130 lat = yc(I,J,bi,bj)-delY(jG) * 0.5 _d 0
131 dxG(I,J,bi,bj) = rSphere*COS(lat*deg2rad)*delX(iG)*deg2rad
132 dyG(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I-1,J,bi,bj))*0.5 _d 0
133 ENDDO
134 ENDDO
135 ENDDO
136 ENDDO
137 _EXCH_XY_R4(dxG, myThid )
138 _EXCH_XY_R4(dyG, myThid )
139 C dxC, dyC is separation between cell centers
140 DO bj = myByLo(myThid), myByHi(myThid)
141 DO bi = myBxLo(myThid), myBxHi(myThid)
142 DO J=1,sNy
143 DO I=1,sNx
144 dxC(I,J,bi,bj) = (dxF(I,J,bi,bj)+dxF(I-1,J,bi,bj))*0.5 _d 0
145 dyC(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I,J-1,bi,bj))*0.5 _d 0
146 ENDDO
147 ENDDO
148 ENDDO
149 ENDDO
150 _EXCH_XY_R4(dxC, myThid )
151 _EXCH_XY_R4(dyC, myThid )
152 C dxV, dyU are separations between velocity points along cell faces.
153 DO bj = myByLo(myThid), myByHi(myThid)
154 DO bi = myBxLo(myThid), myBxHi(myThid)
155 DO J=1,sNy
156 DO I=1,sNx
157 dxV(I,J,bi,bj) = (dxG(I,J,bi,bj)+dxG(I-1,J,bi,bj))*0.5 _d 0
158 #ifdef OLD_UV_GEOMETRY
159 dyU(I,J,bi,bj) = (dyG(I,J,bi,bj)+dyG(I,J-1,bi,bj))*0.5 _d 0
160 #else
161 dyU(I,J,bi,bj) = (dyC(I,J,bi,bj)+dyC(I-1,J,bi,bj))*0.5 _d 0
162 #endif
163 ENDDO
164 ENDDO
165 ENDDO
166 ENDDO
167 _EXCH_XY_R4(dxV, myThid )
168 _EXCH_XY_R4(dyU, myThid )
169 C Calculate vertical face area and trigonometric terms
170 DO bj = myByLo(myThid), myByHi(myThid)
171 DO bi = myBxLo(myThid), myBxHi(myThid)
172 DO J=1,sNy
173 DO I=1,sNx
174 jG = myYGlobalLo + (bj-1)*sNy + J-1
175 latS = yc(i,j,bi,bj)-delY(jG)*0.5 _d 0
176 latN = yc(i,j,bi,bj)+delY(jG)*0.5 _d 0
177 #ifdef OLD_UV_GEOMETRY
178 rA(I,J,bi,bj) = dyF(I,J,bi,bj)
179 & *rSphere*(SIN(latN*deg2rad)-SIN(latS*deg2rad))
180 #else
181 rA(I,J,bi,bj) = rSphere*delX(iG)*deg2rad
182 & *rSphere*(SIN(latN*deg2rad)-SIN(latS*deg2rad))
183 #endif
184 C Area cannot be zero but sin can be if lat if < -90.
185 IF ( rA(I,J,bi,bj) .LT. 0. ) rA(I,J,bi,bj) = -rA(I,J,bi,bj)
186 tanPhiAtU(i,j,bi,bj)=tan(_yC(i,j,bi,bj)*deg2rad)
187 tanPhiAtV(i,j,bi,bj)=tan(latS*deg2rad)
188 ENDDO
189 ENDDO
190 ENDDO
191 ENDDO
192 _EXCH_XY_R4 (rA , myThid )
193 _EXCH_XY_R4 (tanPhiAtU , myThid )
194 _EXCH_XY_R4 (tanPhiAtV , myThid )
195 DO bj = myByLo(myThid), myByHi(myThid)
196 DO bi = myBxLo(myThid), myBxHi(myThid)
197 DO J=1,sNy
198 DO I=1,sNx
199 iG = myXGlobalLo + (bi-1)*sNx + I-1
200 jG = myYGlobalLo + (bj-1)*sNy + J-1
201 latS = yc(i,j-1,bi,bj)
202 latN = yc(i,j,bi,bj)
203 #ifdef OLD_UV_GEOMETRY
204 rAw(I,J,bi,bj) = 0.5*(rA(I,J,bi,bj)+rA(I-1,J,bi,bj))
205 rAs(I,J,bi,bj) = 0.5*(rA(I,J,bi,bj)+rA(I,J-1,bi,bj))
206 #else
207 rAw(I,J,bi,bj) = 0.5*(rA(I,J,bi,bj)+rA(I-1,J,bi,bj))
208 rAs(I,J,bi,bj) = rSphere*delX(iG)*deg2rad
209 & *rSphere*(SIN(latN*deg2rad)-SIN(latS*deg2rad))
210 #endif
211 ENDDO
212 ENDDO
213 ENDDO
214 ENDDO
215 _EXCH_XY_R4 (rAw , myThid )
216 _EXCH_XY_R4 (rAs , myThid )
217 C
218 RETURN
219 END

  ViewVC Help
Powered by ViewVC 1.1.22