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

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

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


Revision 1.14 - (hide annotations) (download)
Mon Mar 27 22:25:44 2000 UTC (24 years, 1 month ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint27, branch-atmos-merge-start, checkpoint26, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.13: +3 -9 lines
Removed unused variables and fixed some unitialized variables.

1 adcroft 1.14 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_spherical_polar_grid.F,v 1.13 1999/03/16 16:37:42 adcroft Exp $
2 cnh 1.1
3 cnh 1.10 #include "CPP_OPTIONS.h"
4 cnh 1.1
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 adcroft 1.12 IMPLICIT NONE
37 cnh 1.1
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 xBase - South-west corner location for process.
52     C yBase
53     C iG, jG - Global coordinate index. Usually used to hold
54     C the south-west global coordinate of a tile.
55     C bi,bj - Loop counters
56     C zUpper - Temporary arrays holding z coordinates of
57     C zLower upper and lower faces.
58     C xBase - Lower coordinate for this threads cells
59     C yBase
60     C lat, latN, - Temporary variables used to hold latitude
61     C latS values.
62     C I,J,K
63 adcroft 1.14 _RL xG, yG
64 cnh 1.1 _RL xBase, yBase
65     INTEGER iG, jG
66     INTEGER bi, bj
67 adcroft 1.14 INTEGER I, J
68 cnh 1.1 _RL lat, latS, latN
69    
70     C-- Example of inialisation for spherical polar grid
71     C-- First set coordinates of cell centers
72     C This operation is only performed at start up so for more
73     C complex configurations it is usually OK to pass iG, jG to a custom
74     C function and have it return xG and yG.
75     C Set up my local grid first
76     C Note: In the spherical polar case delX and delY are given in
77     C degrees and are relative to some starting latitude and
78     C longitude - phiMin and thetaMin.
79 cnh 1.5 xC0 = thetaMin
80     yC0 = phiMin
81 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
82     jG = myYGlobalLo + (bj-1)*sNy
83     DO bi = myBxLo(myThid), myBxHi(myThid)
84     iG = myXGlobalLo + (bi-1)*sNx
85     yBase = phiMin
86     xBase = thetaMin
87     DO i=1,iG-1
88     xBase = xBase + delX(i)
89     ENDDO
90     DO j=1,jG-1
91     yBase = yBase + delY(j)
92     ENDDO
93     yG = yBase
94     DO J=1,sNy
95     xG = xBase
96     DO I=1,sNx
97     xc(I,J,bi,bj) = xG + delX(iG+i-1)*0.5 _d 0
98     yc(I,J,bi,bj) = yG + delY(jG+j-1)*0.5 _d 0
99     xG = xG + delX(iG+I-1)
100 cnh 1.10 dxF(I,J,bi,bj) = delX(iG+i-1)*deg2rad
101     & *rSphere*COS(yc(I,J,bi,bj)*deg2rad)
102 cnh 1.1 dyF(I,J,bi,bj) = delY(jG+j-1)*deg2rad*rSphere
103     ENDDO
104     yG = yG + delY(jG+J-1)
105     ENDDO
106     ENDDO
107     ENDDO
108     C Now sync. and get edge regions from other threads and/or processes.
109     C Note: We could just set the overlap regions ourselves here but
110     C exchanging edges is safer and is good practice!
111     _EXCH_XY_R4( xc, myThid )
112     _EXCH_XY_R4( yc, myThid )
113     _EXCH_XY_R4(dxF, myThid )
114     _EXCH_XY_R4(dyF, myThid )
115    
116     C-- Calculate separation between other points
117     C dxG, dyG are separations between cell corners along cell faces.
118     DO bj = myByLo(myThid), myByHi(myThid)
119     DO bi = myBxLo(myThid), myBxHi(myThid)
120     DO J=1,sNy
121     DO I=1,sNx
122     jG = myYGlobalLo + (bj-1)*sNy + J-1
123     iG = myXGlobalLo + (bi-1)*sNx + I-1
124     lat = yc(I,J,bi,bj)-delY(jG) * 0.5 _d 0
125     dxG(I,J,bi,bj) = rSphere*COS(lat*deg2rad)*delX(iG)*deg2rad
126     dyG(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I-1,J,bi,bj))*0.5 _d 0
127     ENDDO
128     ENDDO
129     ENDDO
130     ENDDO
131     _EXCH_XY_R4(dxG, myThid )
132     _EXCH_XY_R4(dyG, myThid )
133 adcroft 1.11 C dxC, dyC is separation between cell centers
134 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
135     DO bi = myBxLo(myThid), myBxHi(myThid)
136     DO J=1,sNy
137     DO I=1,sNx
138 adcroft 1.11 dxC(I,J,bi,bj) = (dxF(I,J,bi,bj)+dxF(I-1,J,bi,bj))*0.5 _d 0
139     dyC(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I,J-1,bi,bj))*0.5 _d 0
140 cnh 1.1 ENDDO
141     ENDDO
142     ENDDO
143     ENDDO
144 adcroft 1.11 _EXCH_XY_R4(dxC, myThid )
145     _EXCH_XY_R4(dyC, myThid )
146     C dxV, dyU are separations between velocity points along cell faces.
147 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
148     DO bi = myBxLo(myThid), myBxHi(myThid)
149     DO J=1,sNy
150     DO I=1,sNx
151 adcroft 1.11 dxV(I,J,bi,bj) = (dxG(I,J,bi,bj)+dxG(I-1,J,bi,bj))*0.5 _d 0
152     #ifdef OLD_UV_GEOMETRY
153     dyU(I,J,bi,bj) = (dyG(I,J,bi,bj)+dyG(I,J-1,bi,bj))*0.5 _d 0
154     #else
155     dyU(I,J,bi,bj) = (dyC(I,J,bi,bj)+dyC(I-1,J,bi,bj))*0.5 _d 0
156     #endif
157 cnh 1.1 ENDDO
158     ENDDO
159     ENDDO
160     ENDDO
161 adcroft 1.11 _EXCH_XY_R4(dxV, myThid )
162     _EXCH_XY_R4(dyU, myThid )
163 adcroft 1.6 C Calculate vertical face area and trigonometric terms
164 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
165     DO bi = myBxLo(myThid), myBxHi(myThid)
166     DO J=1,sNy
167     DO I=1,sNx
168     jG = myYGlobalLo + (bj-1)*sNy + J-1
169 adcroft 1.13 iG = myXGlobalLo + (bi-1)*sNx + I-1
170 cnh 1.1 latS = yc(i,j,bi,bj)-delY(jG)*0.5 _d 0
171     latN = yc(i,j,bi,bj)+delY(jG)*0.5 _d 0
172 adcroft 1.11 #ifdef OLD_UV_GEOMETRY
173 cnh 1.8 rA(I,J,bi,bj) = dyF(I,J,bi,bj)
174 cnh 1.1 & *rSphere*(SIN(latN*deg2rad)-SIN(latS*deg2rad))
175 adcroft 1.11 #else
176     rA(I,J,bi,bj) = rSphere*delX(iG)*deg2rad
177     & *rSphere*(SIN(latN*deg2rad)-SIN(latS*deg2rad))
178     #endif
179 cnh 1.10 C Area cannot be zero but sin can be if lat if < -90.
180     IF ( rA(I,J,bi,bj) .LT. 0. ) rA(I,J,bi,bj) = -rA(I,J,bi,bj)
181 adcroft 1.6 tanPhiAtU(i,j,bi,bj)=tan(_yC(i,j,bi,bj)*deg2rad)
182     tanPhiAtV(i,j,bi,bj)=tan(latS*deg2rad)
183 cnh 1.1 ENDDO
184     ENDDO
185     ENDDO
186     ENDDO
187 cnh 1.8 _EXCH_XY_R4 (rA , myThid )
188 cnh 1.5 _EXCH_XY_R4 (tanPhiAtU , myThid )
189     _EXCH_XY_R4 (tanPhiAtV , myThid )
190 adcroft 1.11 DO bj = myByLo(myThid), myByHi(myThid)
191     DO bi = myBxLo(myThid), myBxHi(myThid)
192     DO J=1,sNy
193     DO I=1,sNx
194     iG = myXGlobalLo + (bi-1)*sNx + I-1
195     jG = myYGlobalLo + (bj-1)*sNy + J-1
196     latS = yc(i,j-1,bi,bj)
197     latN = yc(i,j,bi,bj)
198     #ifdef OLD_UV_GEOMETRY
199     rAw(I,J,bi,bj) = 0.5*(rA(I,J,bi,bj)+rA(I-1,J,bi,bj))
200     rAs(I,J,bi,bj) = 0.5*(rA(I,J,bi,bj)+rA(I,J-1,bi,bj))
201     #else
202     rAw(I,J,bi,bj) = 0.5*(rA(I,J,bi,bj)+rA(I-1,J,bi,bj))
203     rAs(I,J,bi,bj) = rSphere*delX(iG)*deg2rad
204     & *rSphere*(SIN(latN*deg2rad)-SIN(latS*deg2rad))
205     #endif
206     ENDDO
207     ENDDO
208     ENDDO
209     ENDDO
210     _EXCH_XY_R4 (rAw , myThid )
211     _EXCH_XY_R4 (rAs , myThid )
212 cnh 1.1 C
213     RETURN
214     END

  ViewVC Help
Powered by ViewVC 1.1.22