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

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

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


Revision 1.20 - (show annotations) (download)
Tue Oct 17 18:52:34 2006 UTC (17 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_post, checkpoint60, checkpoint61, checkpoint58w_post, checkpoint58q_post, mitgcm_mapl_00, checkpoint58r_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint58v_post, checkpoint61f, checkpoint58x_post, checkpoint59j, checkpoint61e, checkpoint58u_post, checkpoint58s_post, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61h
Changes since 1.19: +3 -3 lines
clean-up multi-threaded problems (reported by debugger tcheck on ACES).

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_cartesian_grid.F,v 1.19 2005/07/31 22:07:48 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INI_CARTESIAN_GRID
8 C !INTERFACE:
9 SUBROUTINE INI_CARTESIAN_GRID( myThid )
10 C !DESCRIPTION: \bv
11 C *==========================================================*
12 C | SUBROUTINE INI_CARTESIAN_GRID
13 C | o Initialise model coordinate system
14 C *==========================================================*
15 C | The grid arrays, initialised here, are used throughout
16 C | the code in evaluating gradients, integrals and spatial
17 C | avarages. This routine
18 C | is called separately by each thread and initialises only
19 C | the region of the domain it is "responsible" for.
20 C | Notes:
21 C | Two examples are included. One illustrates the
22 C | initialisation of a cartesian grid (this routine).
23 C | The other shows the
24 C | inialisation of a spherical polar grid. Other orthonormal
25 C | grids can be fitted into this design. In this case
26 C | custom metric terms also need adding to account for the
27 C | projections of velocity vectors onto these grids.
28 C | The structure used here also makes it possible to
29 C | implement less regular grid mappings. In particular
30 C | o Schemes which leave out blocks of the domain that are
31 C | all land could be supported.
32 C | o Multi-level schemes such as icosohedral or cubic
33 C | grid projections onto a sphere can also be fitted
34 C | within the strategy we use.
35 C | Both of the above also require modifying the support
36 C | routines that map computational blocks to simulation
37 C | domain blocks.
38 C | Under the cartesian grid mode primitive distances in X
39 C | and Y are in metres. Disktance in Z are in m or Pa
40 C | depending on the vertical gridding mode.
41 C *==========================================================*
42 C \ev
43
44 C !USES:
45 IMPLICIT NONE
46 C === Global variables ===
47 #include "SIZE.h"
48 #include "EEPARAMS.h"
49 #include "PARAMS.h"
50 #include "GRID.h"
51
52 C !INPUT/OUTPUT PARAMETERS:
53 C == Routine arguments ==
54 C myThid - Number of this instance of INI_CARTESIAN_GRID
55 INTEGER myThid
56
57 C !LOCAL VARIABLES:
58 C == Local variables ==
59 INTEGER iG, jG, bi, bj, I, J
60 _RL xG0, yG0
61 C "Long" real for temporary coordinate calculation
62 C NOTICE the extended range of indices!!
63 _RL xGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
64 _RL yGloc(1-Olx:sNx+Olx+1,1-Oly:sNy+Oly+1)
65 C These functions return the "global" index with valid values beyond
66 C halo regions
67 INTEGER iGl,jGl
68 iGl(I,bi) = 1+mod(myXGlobalLo-1+(bi-1)*sNx+I+Olx*Nx-1,Nx)
69 jGl(J,bj) = 1+mod(myYGlobalLo-1+(bj-1)*sNy+J+Oly*Ny-1,Ny)
70 CEOP
71
72 C For each tile ...
73 DO bj = myByLo(myThid), myByHi(myThid)
74 DO bi = myBxLo(myThid), myBxHi(myThid)
75
76 C-- "Global" index (place holder)
77 jG = myYGlobalLo + (bj-1)*sNy
78 iG = myXGlobalLo + (bi-1)*sNx
79
80 C-- First find coordinate of tile corner (meaning outer corner of halo)
81 xG0 = 0.
82 C Find the X-coordinate of the outer grid-line of the "real" tile
83 DO i=1, iG-1
84 xG0 = xG0 + delX(i)
85 ENDDO
86 C Back-step to the outer grid-line of the "halo" region
87 DO i=1, Olx
88 xG0 = xG0 - delX( 1+mod(Olx*Nx-1+iG-i,Nx) )
89 ENDDO
90 C Find the Y-coordinate of the outer grid-line of the "real" tile
91 yG0 = 0.
92 DO j=1, jG-1
93 yG0 = yG0 + delY(j)
94 ENDDO
95 C Back-step to the outer grid-line of the "halo" region
96 DO j=1, Oly
97 yG0 = yG0 - delY( 1+mod(Oly*Ny-1+jG-j,Ny) )
98 ENDDO
99
100 C-- Calculate coordinates of cell corners for N+1 grid-lines
101 DO J=1-Oly,sNy+Oly +1
102 xGloc(1-Olx,J) = xG0
103 DO I=1-Olx,sNx+Olx
104 c xGloc(I+1,J) = xGloc(I,J) + delX(1+mod(Nx-1+iG-1+i,Nx))
105 xGloc(I+1,J) = xGloc(I,J) + delX( iGl(I,bi) )
106 ENDDO
107 ENDDO
108 DO I=1-Olx,sNx+Olx +1
109 yGloc(I,1-Oly) = yG0
110 DO J=1-Oly,sNy+Oly
111 c yGloc(I,J+1) = yGloc(I,J) + delY(1+mod(Ny-1+jG-1+j,Ny))
112 yGloc(I,J+1) = yGloc(I,J) + delY( jGl(J,bj) )
113 ENDDO
114 ENDDO
115
116 C-- Make a permanent copy of [xGloc,yGloc] in [xG,yG]
117 DO J=1-Oly,sNy+Oly
118 DO I=1-Olx,sNx+Olx
119 xG(I,J,bi,bj) = xGloc(I,J)
120 yG(I,J,bi,bj) = yGloc(I,J)
121 ENDDO
122 ENDDO
123
124 C-- Calculate [xC,yC], coordinates of cell centers
125 DO J=1-Oly,sNy+Oly
126 DO I=1-Olx,sNx+Olx
127 C by averaging
128 xC(I,J,bi,bj) = 0.25*(
129 & xGloc(I,J)+xGloc(I+1,J)+xGloc(I,J+1)+xGloc(I+1,J+1) )
130 yC(I,J,bi,bj) = 0.25*(
131 & yGloc(I,J)+yGloc(I+1,J)+yGloc(I,J+1)+yGloc(I+1,J+1) )
132 ENDDO
133 ENDDO
134
135 C-- Calculate [dxF,dyF], lengths between cell faces (through center)
136 DO J=1-Oly,sNy+Oly
137 DO I=1-Olx,sNx+Olx
138 dXF(I,J,bi,bj) = delX( iGl(I,bi) )
139 dYF(I,J,bi,bj) = delY( jGl(J,bj) )
140 ENDDO
141 ENDDO
142
143 C-- Calculate [dxG,dyG], lengths along cell boundaries
144 DO J=1-Oly,sNy+Oly
145 DO I=1-Olx,sNx+Olx
146 dXG(I,J,bi,bj) = delX( iGl(I,bi) )
147 dYG(I,J,bi,bj) = delY( jGl(J,bj) )
148 ENDDO
149 ENDDO
150
151 C-- The following arrays are not defined in some parts of the halo
152 C region. We set them to zero here for safety. If they are ever
153 C referred to, especially in the denominator then it is a mistake!
154 DO J=1-Oly,sNy+Oly
155 DO I=1-Olx,sNx+Olx
156 dXC(I,J,bi,bj) = 0.
157 dYC(I,J,bi,bj) = 0.
158 dXV(I,J,bi,bj) = 0.
159 dYU(I,J,bi,bj) = 0.
160 rAw(I,J,bi,bj) = 0.
161 rAs(I,J,bi,bj) = 0.
162 ENDDO
163 ENDDO
164
165 C-- Calculate [dxC], zonal length between cell centers
166 DO J=1-Oly,sNy+Oly
167 DO I=1-Olx+1,sNx+Olx ! NOTE range
168 dXC(I,J,bi,bj) = 0.5D0*(dXF(I,J,bi,bj)+dXF(I-1,J,bi,bj))
169 ENDDO
170 ENDDO
171
172 C-- Calculate [dyC], meridional length between cell centers
173 DO J=1-Oly+1,sNy+Oly ! NOTE range
174 DO I=1-Olx,sNx+Olx
175 dYC(I,J,bi,bj) = 0.5*(dYF(I,J,bi,bj)+dYF(I,J-1,bi,bj))
176 ENDDO
177 ENDDO
178
179 C-- Calculate [dxV,dyU], length between velocity points (through corners)
180 DO J=1-Oly+1,sNy+Oly ! NOTE range
181 DO I=1-Olx+1,sNx+Olx ! NOTE range
182 C by averaging (method I)
183 dXV(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I-1,J,bi,bj))
184 dYU(I,J,bi,bj) = 0.5*(dYG(I,J,bi,bj)+dYG(I,J-1,bi,bj))
185 C by averaging (method II)
186 c dXV(I,J,bi,bj) = 0.5*(dXG(I,J,bi,bj)+dXG(I-1,J,bi,bj))
187 c dYU(I,J,bi,bj) = 0.5*(dYC(I,J,bi,bj)+dYC(I-1,J,bi,bj))
188 ENDDO
189 ENDDO
190
191 C-- Calculate vertical face area
192 DO J=1-Oly,sNy+Oly
193 DO I=1-Olx,sNx+Olx
194 rA (I,J,bi,bj) = dxF(I,J,bi,bj)*dyF(I,J,bi,bj)
195 rAw(I,J,bi,bj) = dxC(I,J,bi,bj)*dyG(I,J,bi,bj)
196 rAs(I,J,bi,bj) = dxG(I,J,bi,bj)*dyC(I,J,bi,bj)
197 rAz(I,J,bi,bj) = dxV(I,J,bi,bj)*dyU(I,J,bi,bj)
198 C-- Set trigonometric terms & grid orientation:
199 tanPhiAtU(I,J,bi,bj) = 0.
200 tanPhiAtV(I,J,bi,bj) = 0.
201 angleCosC(I,J,bi,bj) = 1.
202 angleSinC(I,J,bi,bj) = 0.
203 ENDDO
204 ENDDO
205
206 C-- Cosine(lat) scaling
207 DO J=1-OLy,sNy+OLy
208 cosFacU(J,bi,bj)=1.
209 cosFacV(J,bi,bj)=1.
210 sqcosFacU(J,bi,bj)=1.
211 sqcosFacV(J,bi,bj)=1.
212 ENDDO
213
214 ENDDO ! bi
215 ENDDO ! bj
216
217 C-- Set default (=whole domain) for where relaxation to climatology applies
218 _BEGIN_MASTER(myThid)
219 IF ( latBandClimRelax.EQ.UNSET_RL ) THEN
220 latBandClimRelax = 0.
221 DO j=1,Ny
222 latBandClimRelax = latBandClimRelax + delY(j)
223 ENDDO
224 latBandClimRelax = latBandClimRelax*3. _d 0
225 ENDIF
226 _END_MASTER(myThid)
227
228 RETURN
229 END

  ViewVC Help
Powered by ViewVC 1.1.22