/[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.6 - (hide annotations) (download)
Mon Jun 22 15:26:25 1998 UTC (25 years, 11 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint10, checkpoint9, checkpoint8
Changes since 1.5: +4 -8 lines
Various changes including time-dependant forcing:
 o logic for controlling external forcing fields now allows
   for time-dependant forcing: load_external_fields.F
 o genmake.dec needed a special line for the above file.
 o theta* and salt* time-stepping algorithm were re-implemented.
The 4x4 global configuration has been "double-checked" against
CNH's version. However, we do not assume any responsibility for
the correctness of this code ...  8-)

1 adcroft 1.6 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_spherical_polar_grid.F,v 1.5 1998/06/08 21:43:01 cnh Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.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    
37     C === Global variables ===
38     #include "SIZE.h"
39     #include "EEPARAMS.h"
40     #include "PARAMS.h"
41     #include "GRID.h"
42    
43     C == Routine arguments ==
44     C myThid - Number of this instance of INI_CARTESIAN_GRID
45     INTEGER myThid
46     CEndOfInterface
47    
48     C == Local variables ==
49     C xG, yG - Global coordinate location.
50     C zG
51     C xBase - South-west corner location for process.
52     C yBase
53     C zUpper - Work arrays for upper and lower
54     C zLower cell-face heights.
55     C phi - Temporary scalar
56     C iG, jG - Global coordinate index. Usually used to hold
57     C the south-west global coordinate of a tile.
58     C bi,bj - Loop counters
59     C zUpper - Temporary arrays holding z coordinates of
60     C zLower upper and lower faces.
61     C xBase - Lower coordinate for this threads cells
62     C yBase
63     C lat, latN, - Temporary variables used to hold latitude
64     C latS values.
65     C I,J,K
66     _RL xG, yG, zG
67     _RL phi
68     _RL zUpper(Nz), zLower(Nz)
69     _RL xBase, yBase
70     INTEGER iG, jG
71     INTEGER bi, bj
72     INTEGER I, J, K
73     _RL lat, latS, latN
74    
75     C-- Example of inialisation for spherical polar grid
76     C-- First set coordinates of cell centers
77     C This operation is only performed at start up so for more
78     C complex configurations it is usually OK to pass iG, jG to a custom
79     C function and have it return xG and yG.
80     C Set up my local grid first
81     C Note: In the spherical polar case delX and delY are given in
82     C degrees and are relative to some starting latitude and
83     C longitude - phiMin and thetaMin.
84 cnh 1.5 xC0 = thetaMin
85     yC0 = phiMin
86 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
87     jG = myYGlobalLo + (bj-1)*sNy
88     DO bi = myBxLo(myThid), myBxHi(myThid)
89     iG = myXGlobalLo + (bi-1)*sNx
90     yBase = phiMin
91     xBase = thetaMin
92     DO i=1,iG-1
93     xBase = xBase + delX(i)
94     ENDDO
95     DO j=1,jG-1
96     yBase = yBase + delY(j)
97     ENDDO
98     yG = yBase
99     DO J=1,sNy
100     xG = xBase
101     DO I=1,sNx
102     xc(I,J,bi,bj) = xG + delX(iG+i-1)*0.5 _d 0
103     yc(I,J,bi,bj) = yG + delY(jG+j-1)*0.5 _d 0
104     xG = xG + delX(iG+I-1)
105     dxF(I,J,bi,bj) = delX(iG+i-1)*deg2rad*rSphere*COS(yc(I,J,bi,bj)*deg2rad)
106     dyF(I,J,bi,bj) = delY(jG+j-1)*deg2rad*rSphere
107     ENDDO
108     yG = yG + delY(jG+J-1)
109     ENDDO
110     ENDDO
111     ENDDO
112     C Now sync. and get edge regions from other threads and/or processes.
113     C Note: We could just set the overlap regions ourselves here but
114     C exchanging edges is safer and is good practice!
115     _EXCH_XY_R4( xc, myThid )
116     _EXCH_XY_R4( yc, myThid )
117     _EXCH_XY_R4(dxF, myThid )
118     _EXCH_XY_R4(dyF, myThid )
119    
120     C-- Calculate separation between other points
121     C dxG, dyG are separations between cell corners along cell faces.
122     DO bj = myByLo(myThid), myByHi(myThid)
123     DO bi = myBxLo(myThid), myBxHi(myThid)
124     DO J=1,sNy
125     DO I=1,sNx
126     jG = myYGlobalLo + (bj-1)*sNy + J-1
127     iG = myXGlobalLo + (bi-1)*sNx + I-1
128     lat = yc(I,J,bi,bj)-delY(jG) * 0.5 _d 0
129     dxG(I,J,bi,bj) = rSphere*COS(lat*deg2rad)*delX(iG)*deg2rad
130     dyG(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I-1,J,bi,bj))*0.5 _d 0
131     ENDDO
132     ENDDO
133     ENDDO
134     ENDDO
135     _EXCH_XY_R4(dxG, myThid )
136     _EXCH_XY_R4(dyG, myThid )
137     C dxV, dyU are separations between velocity points along cell faces.
138     DO bj = myByLo(myThid), myByHi(myThid)
139     DO bi = myBxLo(myThid), myBxHi(myThid)
140     DO J=1,sNy
141     DO I=1,sNx
142     dxV(I,J,bi,bj) = (dxG(I,J,bi,bj)+dxG(I-1,J,bi,bj))*0.5 _d 0
143     dyU(I,J,bi,bj) = (dyG(I,J,bi,bj)+dyG(I,J-1,bi,bj))*0.5 _d 0
144     ENDDO
145     ENDDO
146     ENDDO
147     ENDDO
148     _EXCH_XY_R4(dxV, myThid )
149     _EXCH_XY_R4(dyU, myThid )
150     C dxC, dyC is separation between cell centers
151     DO bj = myByLo(myThid), myByHi(myThid)
152     DO bi = myBxLo(myThid), myBxHi(myThid)
153     DO J=1,sNy
154     DO I=1,sNx
155     dxC(I,J,bi,bj) = (dxF(I,J,bi,bj)+dxF(I-1,J,bi,bj))*0.5 _d 0
156     dyC(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I,J-1,bi,bj))*0.5 _d 0
157     ENDDO
158     ENDDO
159     ENDDO
160     ENDDO
161     _EXCH_XY_R4(dxC, myThid )
162     _EXCH_XY_R4(dyC, myThid )
163     C Calculate recipricols
164     DO bj = myByLo(myThid), myByHi(myThid)
165     DO bi = myBxLo(myThid), myBxHi(myThid)
166     DO J=1,sNy
167     DO I=1,sNx
168     rDxG(I,J,bi,bj)=1.d0/dxG(I,J,bi,bj)
169     rDyG(I,J,bi,bj)=1.d0/dyG(I,J,bi,bj)
170     rDxC(I,J,bi,bj)=1.d0/dxC(I,J,bi,bj)
171     rDyC(I,J,bi,bj)=1.d0/dyC(I,J,bi,bj)
172     rDxF(I,J,bi,bj)=1.d0/dxF(I,J,bi,bj)
173     rDyF(I,J,bi,bj)=1.d0/dyF(I,J,bi,bj)
174     rDxV(I,J,bi,bj)=1.d0/dxV(I,J,bi,bj)
175     rDyU(I,J,bi,bj)=1.d0/dyU(I,J,bi,bj)
176     ENDDO
177     ENDDO
178     ENDDO
179     ENDDO
180     _EXCH_XY_R4(rDxG, myThid )
181     _EXCH_XY_R4(rDyG, myThid )
182     _EXCH_XY_R4(rDxC, myThid )
183     _EXCH_XY_R4(rDyC, myThid )
184     _EXCH_XY_R4(rDxF, myThid )
185     _EXCH_XY_R4(rDyF, myThid )
186     _EXCH_XY_R4(rDxV, myThid )
187     _EXCH_XY_R4(rDyU, myThid )
188 adcroft 1.6 C Calculate vertical face area and trigonometric terms
189 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
190     DO bi = myBxLo(myThid), myBxHi(myThid)
191     DO J=1,sNy
192     DO I=1,sNx
193     jG = myYGlobalLo + (bj-1)*sNy + J-1
194     latS = yc(i,j,bi,bj)-delY(jG)*0.5 _d 0
195     latN = yc(i,j,bi,bj)+delY(jG)*0.5 _d 0
196     zA(I,J,bi,bj) = dyF(I,J,bi,bj)
197     & *rSphere*(SIN(latN*deg2rad)-SIN(latS*deg2rad))
198 adcroft 1.6 tanPhiAtU(i,j,bi,bj)=tan(_yC(i,j,bi,bj)*deg2rad)
199     tanPhiAtV(i,j,bi,bj)=tan(latS*deg2rad)
200 cnh 1.1 ENDDO
201     ENDDO
202     ENDDO
203     ENDDO
204 cnh 1.5
205     DO bj = myByLo(myThid), myByHi(myThid)
206     DO bi = myBxLo(myThid), myBxHi(myThid)
207     DO K=1,Nz
208     DO J=1,sNy
209     DO I=1,sNx
210     IF (HFacC(I,J,K,bi,bj) .NE. 0. D0 ) THEN
211     rHFacC(I,J,K,bi,bj) = 1. D0 / HFacC(I,J,K,bi,bj)
212     ELSE
213     rHFacC(I,J,K,bi,bj) = 0. D0
214     ENDIF
215     IF (HFacW(I,J,K,bi,bj) .NE. 0. D0 ) THEN
216     rHFacW(I,J,K,bi,bj) = 1. D0 / HFacW(I,J,K,bi,bj)
217     maskW(I,J,K,bi,bj) = 1. D0
218     ELSE
219     rHFacW(I,J,K,bi,bj) = 0. D0
220     maskW(I,J,K,bi,bj) = 0.0 D0
221     ENDIF
222     IF (HFacS(I,J,K,bi,bj) .NE. 0. D0 ) THEN
223     rHFacS(I,J,K,bi,bj) = 1. D0 / HFacS(I,J,K,bi,bj)
224     maskS(I,J,K,bi,bj) = 1. D0
225     ELSE
226     rHFacS(I,J,K,bi,bj) = 0. D0
227     maskS(I,J,K,bi,bj) = 0. D0
228     ENDIF
229     ENDDO
230     ENDDO
231     ENDDO
232     ENDDO
233     ENDDO
234     C Now sync. and get/send edge regions that are shared with
235     C other threads.
236     _EXCH_XYZ_R4(rHFacC , myThid )
237     _EXCH_XYZ_R4(rHFacW , myThid )
238     _EXCH_XYZ_R4(rHFacS , myThid )
239     _EXCH_XYZ_R4(maskW , myThid )
240     _EXCH_XYZ_R4(maskS , myThid )
241     _EXCH_XY_R4 (zA , myThid )
242     _EXCH_XY_R4 (tanPhiAtU , myThid )
243     _EXCH_XY_R4 (tanPhiAtV , myThid )
244    
245 cnh 1.1 C
246     RETURN
247     END

  ViewVC Help
Powered by ViewVC 1.1.22