/[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.16 - (hide annotations) (download)
Tue May 29 14:01:37 2001 UTC (23 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5, checkpoint40
Changes since 1.15: +140 -110 lines
Merge from branch pre38:
 o essential mods for cubed sphere
 o debugged atmosphere, dynamcis + physics (aim)
 o new packages (mom_vecinv, mom_fluxform, ...)

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

  ViewVC Help
Powered by ViewVC 1.1.22