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

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

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


Revision 1.6 - (hide annotations) (download)
Thu Jun 25 20:43:23 1998 UTC (25 years, 11 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint10
Changes since 1.5: +11 -5 lines
Changes to make compatible with DEC F77 compiler

1 cnh 1.6 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_cartesian_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_CARTESIAN_GRID( myThid )
7     C /==========================================================\
8     C | SUBROUTINE INI_CARTESIAN_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 cartesian grid mode primitive distances in X |
33     C | and Y are in metres. Disktance 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 xBase - Temporaries for lower corner coordinate
57     C yBase
58     C iG, jG - Global coordinate index. Usually used to hold
59     C the south-west global coordinate of a tile.
60     C bi,bj - Loop counters
61     C zUpper - Temporary arrays holding z coordinates of
62     C zLower upper and lower faces.
63     C I,J,K
64     _RL xG, yG, zG
65     _RL phi
66     _RL zUpper(Nz), zLower(Nz)
67     _RL xBase, yBase
68     INTEGER iG, jG
69     INTEGER bi, bj
70     INTEGER I, J, K
71    
72     C-- Simple example of inialisation on cartesian grid
73     C-- First set coordinates of cell centers
74     C This operation is only performed at start up so for more
75     C complex configurations it is usually OK to pass iG, jG to a custom
76     C function and have it return xG and yG.
77     C Set up my local grid first
78 cnh 1.5 xC0 = 0. _d 0
79     yC0 = 0. _d 0
80 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
81     jG = myYGlobalLo + (bj-1)*sNy
82     DO bi = myBxLo(myThid), myBxHi(myThid)
83     iG = myXGlobalLo + (bi-1)*sNx
84     yBase = 0. _d 0
85     xBase = 0. _d 0
86     DO i=1,iG-1
87     xBase = xBase + delX(i)
88     ENDDO
89     DO j=1,jG-1
90     yBase = yBase + delY(j)
91     ENDDO
92     yG = yBase
93     DO J=1,sNy
94     xG = xBase
95     DO I=1,sNx
96     xc(I,J,bi,bj) = xG + delX(iG+i-1)*0.5 _d 0
97     yc(I,J,bi,bj) = yG + delY(jG+j-1)*0.5 _d 0
98     xG = xG + delX(iG+I-1)
99     dxF(I,J,bi,bj) = delX(iG+i-1)
100     dyF(I,J,bi,bj) = delY(jG+j-1)
101     ENDDO
102     yG = yG + delY(jG+J-1)
103     ENDDO
104     ENDDO
105     ENDDO
106     C Now sync. and get edge regions from other threads and/or processes.
107     C Note: We could just set the overlap regions ourselves here but
108     C exchanging edges is safer and is good practice!
109     _EXCH_XY_R4( xc, myThid )
110     _EXCH_XY_R4( yc, myThid )
111     _EXCH_XY_R4(dxF, myThid )
112     _EXCH_XY_R4(dyF, myThid )
113    
114     C-- Calculate separation between other points
115     C dxG, dyG are separations between cell corners along cell faces.
116     DO bj = myByLo(myThid), myByHi(myThid)
117     DO bi = myBxLo(myThid), myBxHi(myThid)
118     DO J=1,sNy
119     DO I=1,sNx
120     dxG(I,J,bi,bj) = (dxF(I,J,bi,bj)+dxF(I,J-1,bi,bj))*0.5 _d 0
121     dyG(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I-1,J,bi,bj))*0.5 _d 0
122     ENDDO
123     ENDDO
124     ENDDO
125     ENDDO
126     _EXCH_XY_R4(dxG, myThid )
127     _EXCH_XY_R4(dyG, myThid )
128     C dxV, dyU are separations between velocity points along cell faces.
129     DO bj = myByLo(myThid), myByHi(myThid)
130     DO bi = myBxLo(myThid), myBxHi(myThid)
131     DO J=1,sNy
132     DO I=1,sNx
133     dxV(I,J,bi,bj) = (dxG(I,J,bi,bj)+dxG(I-1,J,bi,bj))*0.5 _d 0
134     dyU(I,J,bi,bj) = (dyG(I,J,bi,bj)+dyG(I,J-1,bi,bj))*0.5 _d 0
135     ENDDO
136     ENDDO
137     ENDDO
138     ENDDO
139     _EXCH_XY_R4(dxV, myThid )
140     _EXCH_XY_R4(dyU, myThid )
141     C dxC, dyC is separation between cell centers
142     DO bj = myByLo(myThid), myByHi(myThid)
143     DO bi = myBxLo(myThid), myBxHi(myThid)
144     DO J=1,sNy
145     DO I=1,sNx
146     dxC(I,J,bi,bj) = (dxF(I,J,bi,bj)+dxF(I-1,J,bi,bj))*0.5 D0
147     dyC(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I,J-1,bi,bj))*0.5 D0
148     ENDDO
149     ENDDO
150     ENDDO
151     ENDDO
152     _EXCH_XY_R4(dxC, myThid )
153     _EXCH_XY_R4(dyC, myThid )
154     C Calculate recipricols
155     DO bj = myByLo(myThid), myByHi(myThid)
156     DO bi = myBxLo(myThid), myBxHi(myThid)
157     DO J=1,sNy
158     DO I=1,sNx
159     rDxG(I,J,bi,bj)=1.d0/dxG(I,J,bi,bj)
160     rDyG(I,J,bi,bj)=1.d0/dyG(I,J,bi,bj)
161     rDxC(I,J,bi,bj)=1.d0/dxC(I,J,bi,bj)
162     rDyC(I,J,bi,bj)=1.d0/dyC(I,J,bi,bj)
163     rDxF(I,J,bi,bj)=1.d0/dxF(I,J,bi,bj)
164     rDyF(I,J,bi,bj)=1.d0/dyF(I,J,bi,bj)
165     rDxV(I,J,bi,bj)=1.d0/dxV(I,J,bi,bj)
166     rDyU(I,J,bi,bj)=1.d0/dyU(I,J,bi,bj)
167     ENDDO
168     ENDDO
169     ENDDO
170     ENDDO
171     _EXCH_XY_R4(rDxG, myThid )
172     _EXCH_XY_R4(rDyG, myThid )
173     _EXCH_XY_R4(rDxC, myThid )
174     _EXCH_XY_R4(rDyC, myThid )
175     _EXCH_XY_R4(rDxF, myThid )
176     _EXCH_XY_R4(rDyF, myThid )
177     _EXCH_XY_R4(rDxV, myThid )
178     _EXCH_XY_R4(rDyU, myThid )
179     C Calculate vertical face area
180     DO bj = myByLo(myThid), myByHi(myThid)
181     DO bi = myBxLo(myThid), myBxHi(myThid)
182     DO J=1,sNy
183     DO I=1,sNx
184     zA(I,J,bi,bj) = dxF(I,J,bi,bj)*dyF(I,J,bi,bj)
185     ENDDO
186     ENDDO
187     ENDDO
188     ENDDO
189    
190     DO bj = myByLo(myThid), myByHi(myThid)
191     DO bi = myBxLo(myThid), myBxHi(myThid)
192     DO K=1,Nz
193     DO J=1,sNy
194     DO I=1,sNx
195     IF (HFacC(I,J,K,bi,bj) .NE. 0. D0 ) THEN
196     rHFacC(I,J,K,bi,bj) = 1. D0 / HFacC(I,J,K,bi,bj)
197     ELSE
198     rHFacC(I,J,K,bi,bj) = 0. D0
199     ENDIF
200     IF (HFacW(I,J,K,bi,bj) .NE. 0. D0 ) THEN
201     rHFacW(I,J,K,bi,bj) = 1. D0 / HFacW(I,J,K,bi,bj)
202     maskW(I,J,K,bi,bj) = 1. D0
203     ELSE
204     rHFacW(I,J,K,bi,bj) = 0. D0
205     maskW(I,J,K,bi,bj) = 0.0 D0
206     ENDIF
207     IF (HFacS(I,J,K,bi,bj) .NE. 0. D0 ) THEN
208     rHFacS(I,J,K,bi,bj) = 1. D0 / HFacS(I,J,K,bi,bj)
209     maskS(I,J,K,bi,bj) = 1. D0
210     ELSE
211     rHFacS(I,J,K,bi,bj) = 0. D0
212     maskS(I,J,K,bi,bj) = 0. D0
213     ENDIF
214     ENDDO
215     ENDDO
216     ENDDO
217     ENDDO
218     ENDDO
219     C Now sync. and get/send edge regions that are shared with
220     C other threads.
221     _EXCH_XYZ_R4(rHFacC , myThid )
222     _EXCH_XYZ_R4(rHFacW , myThid )
223     _EXCH_XYZ_R4(rHFacS , myThid )
224     _EXCH_XYZ_R4(maskW , myThid )
225     _EXCH_XYZ_R4(maskS , myThid )
226 cnh 1.4 _EXCH_XY_R4 (zA , myThid )
227 cnh 1.5
228 cnh 1.6 DO bj = myByLo(myThid), myByHi(myThid)
229     DO bi = myBxLo(myThid), myBxHi(myThid)
230     DO J=1,sNy
231     DO I=1,sNx
232     tanPhiAtU(I,J,bi,bj) = 0. _d 0
233     tanPhiAtV(I,J,bi,bj) = 0. _d 0
234     ENDDO
235     ENDDO
236     ENDDO
237     ENDDO
238 cnh 1.5 _EXCH_XY_R4 (tanPhiAtU , myThid )
239     _EXCH_XY_R4 (tanPhiAtV , myThid )
240 cnh 1.1
241     C
242     RETURN
243     END

  ViewVC Help
Powered by ViewVC 1.1.22