/[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.12 - (hide annotations) (download)
Wed Dec 9 16:11:52 1998 UTC (25 years, 5 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint19, checkpoint20, checkpoint21, checkpoint22, checkpoint23, checkpoint24, checkpoint25
Changes since 1.11: +2 -1 lines
Added IMPLICIT NONE in a lot of subroutines.
Also corrected the recip_Rhonil bug: we didn't set it in ini_parms.F

1 adcroft 1.12 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_cartesian_grid.F,v 1.11 1998/11/30 23:45:24 adcroft Exp $
2 cnh 1.1
3 cnh 1.10 #include "CPP_OPTIONS.h"
4 cnh 1.1
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 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 zG
52     C xBase - South-west corner location for process.
53     C yBase
54     C zUpper - Work arrays for upper and lower
55     C zLower cell-face heights.
56     C phi - Temporary scalar
57     C xBase - Temporaries for lower corner coordinate
58     C yBase
59     C iG, jG - Global coordinate index. Usually used to hold
60     C the south-west global coordinate of a tile.
61     C bi,bj - Loop counters
62     C zUpper - Temporary arrays holding z coordinates of
63     C zLower upper and lower faces.
64     C I,J,K
65     _RL xG, yG, zG
66     _RL phi
67 cnh 1.8 _RL zUpper(Nr), zLower(Nr)
68 cnh 1.1 _RL xBase, yBase
69     INTEGER iG, jG
70     INTEGER bi, bj
71     INTEGER I, J, K
72    
73     C-- Simple example of inialisation on cartesian grid
74     C-- First set coordinates of cell centers
75     C This operation is only performed at start up so for more
76     C complex configurations it is usually OK to pass iG, jG to a custom
77     C function and have it return xG and yG.
78     C Set up my local grid first
79 cnh 1.5 xC0 = 0. _d 0
80     yC0 = 0. _d 0
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 = 0. _d 0
86     xBase = 0. _d 0
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     dxF(I,J,bi,bj) = delX(iG+i-1)
101     dyF(I,J,bi,bj) = delY(jG+j-1)
102     ENDDO
103     yG = yG + delY(jG+J-1)
104     ENDDO
105     ENDDO
106     ENDDO
107     C Now sync. and get edge regions from other threads and/or processes.
108     C Note: We could just set the overlap regions ourselves here but
109     C exchanging edges is safer and is good practice!
110     _EXCH_XY_R4( xc, myThid )
111     _EXCH_XY_R4( yc, myThid )
112     _EXCH_XY_R4(dxF, myThid )
113     _EXCH_XY_R4(dyF, myThid )
114    
115     C-- Calculate separation between other points
116     C dxG, dyG are separations between cell corners along cell faces.
117     DO bj = myByLo(myThid), myByHi(myThid)
118     DO bi = myBxLo(myThid), myBxHi(myThid)
119     DO J=1,sNy
120     DO I=1,sNx
121     dxG(I,J,bi,bj) = (dxF(I,J,bi,bj)+dxF(I,J-1,bi,bj))*0.5 _d 0
122     dyG(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I-1,J,bi,bj))*0.5 _d 0
123     ENDDO
124     ENDDO
125     ENDDO
126     ENDDO
127     _EXCH_XY_R4(dxG, myThid )
128     _EXCH_XY_R4(dyG, myThid )
129     C dxV, dyU are separations between velocity points along cell faces.
130     DO bj = myByLo(myThid), myByHi(myThid)
131     DO bi = myBxLo(myThid), myBxHi(myThid)
132     DO J=1,sNy
133     DO I=1,sNx
134     dxV(I,J,bi,bj) = (dxG(I,J,bi,bj)+dxG(I-1,J,bi,bj))*0.5 _d 0
135     dyU(I,J,bi,bj) = (dyG(I,J,bi,bj)+dyG(I,J-1,bi,bj))*0.5 _d 0
136     ENDDO
137     ENDDO
138     ENDDO
139     ENDDO
140     _EXCH_XY_R4(dxV, myThid )
141     _EXCH_XY_R4(dyU, myThid )
142     C dxC, dyC is separation between cell centers
143     DO bj = myByLo(myThid), myByHi(myThid)
144     DO bi = myBxLo(myThid), myBxHi(myThid)
145     DO J=1,sNy
146     DO I=1,sNx
147 cnh 1.9 dxC(I,J,bi,bj) = (dxF(I,J,bi,bj)+dxF(I-1,J,bi,bj))*0.5 _d 0
148     dyC(I,J,bi,bj) = (dyF(I,J,bi,bj)+dyF(I,J-1,bi,bj))*0.5 _d 0
149 cnh 1.1 ENDDO
150     ENDDO
151     ENDDO
152     ENDDO
153     _EXCH_XY_R4(dxC, myThid )
154     _EXCH_XY_R4(dyC, myThid )
155     C Calculate vertical face area
156     DO bj = myByLo(myThid), myByHi(myThid)
157     DO bi = myBxLo(myThid), myBxHi(myThid)
158     DO J=1,sNy
159     DO I=1,sNx
160 adcroft 1.11 rA (I,J,bi,bj) = dxF(I,J,bi,bj)*dyF(I,J,bi,bj)
161     rAw(I,J,bi,bj) = dxC(I,J,bi,bj)*dyG(I,J,bi,bj)
162     rAs(I,J,bi,bj) = dxG(I,J,bi,bj)*dyC(I,J,bi,bj)
163 cnh 1.6 tanPhiAtU(I,J,bi,bj) = 0. _d 0
164     tanPhiAtV(I,J,bi,bj) = 0. _d 0
165     ENDDO
166     ENDDO
167     ENDDO
168     ENDDO
169 cnh 1.8 _EXCH_XY_R4 (rA , myThid )
170 adcroft 1.11 _EXCH_XY_R4 (rAw , myThid )
171     _EXCH_XY_R4 (rAs , myThid )
172 cnh 1.5 _EXCH_XY_R4 (tanPhiAtU , myThid )
173     _EXCH_XY_R4 (tanPhiAtV , myThid )
174 cnh 1.1
175     C
176     RETURN
177     END

  ViewVC Help
Powered by ViewVC 1.1.22