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

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

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


Revision 1.1 - (show annotations) (download)
Wed Apr 22 19:15:30 1998 UTC (26 years, 1 month ago) by cnh
Branch: MAIN
Branch point for: cnh
Initial revision

1 C $Id$
2
3 #include "CPP_EEOPTIONS.h"
4
5 CStartOfInterface
6 SUBROUTINE INI_DEPTHS( myThid )
7 C /==========================================================\
8 C | SUBROUTINE INI_DEPTHS |
9 C | o Initialise map of model depths |
10 C |==========================================================|
11 C | The depths of the bottom of the model is specified in |
12 C | terms of an XY map with one depth for each column of |
13 C | grid cells. Depths do not have to coincide with the |
14 C | model levels. The model's lopping algorithm makes it |
15 C | possible to represent arbitrary depths. |
16 C | The mode depths map also influences the models topology |
17 C | By default the model domain wraps around in X and Y. |
18 C | This default doubly periodic topology is "supressed" |
19 C | if a depth map is defined which closes off all wrap |
20 C | around flow. |
21 C \==========================================================/
22
23 C === Global variables ===
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "GRID.h"
28
29 C == Routine arguments ==
30 C myThid - Number of this instance of INI_DEPTHS
31 INTEGER myThid
32 CEndOfInterface
33
34 C == Local variables ==
35 C xG, yG - Global coordinate location.
36 C zG
37 C zUpper - Work arrays for upper and lower
38 C zLower cell-face heights.
39 C phi - Temporary scalar
40 C iG, jG - Global coordinate index
41 C bi,bj - Loop counters
42 C zUpper - Temporary arrays holding z coordinates of
43 C zLower upper and lower faces.
44 C I,J,K
45 _RL xG, yG, zG
46 _RL phi
47 _RL zUpper(Nz), zLower(Nz)
48 INTEGER iG, jG
49 INTEGER bi, bj
50 INTEGER I, J, K
51
52 C For now set up a flat bottom box with doubly periodic topology.
53 C H is the basic variable from which other terms are derived. It
54 C is the term that would be set from an external file for a
55 C realistic problem.
56 _BARRIER
57 phi = 0. D0
58 DO K=1,Nz
59 phi = phi+delZ(K)
60 ENDDO
61 DO bj = myByLo(myThid), myByHi(myThid)
62 DO bi = myBxLo(myThid), myBxHi(myThid)
63 DO j=1,sNy
64 DO i=1,sNx
65 iG = myXGlobalLo-1+(bi-1)*sNx+I
66 jG = myYGlobalLo-1+(bj-1)*sNy+J
67 C Default depth of full domain
68 H(i,j,bi,bj) = phi
69 C Test for eastern edge
70 IF ( iG .EQ. nX ) H(i,j,bi,bj) = 0.
71 C Test for northern edge
72 IF ( jG .EQ. nY ) H(i,j,bi,bj) = 0.
73 C Island
74 C IF ( iG .EQ. 1 .AND.
75 C & jG .EQ. 24 ) H(i,j,bi,bj) = 0.
76
77 ENDDO
78 ENDDO
79 ENDDO
80 ENDDO
81 DO bj = myByLo(myThid), myByHi(myThid)
82 DO bi = myBxLo(myThid), myBxHi(myThid)
83 DO J=1,sNy
84 DO I=1,sNx
85 C Inverse of depth
86 IF ( h(i,j,bi,bj) .EQ. 0. _d 0 ) THEN
87 rH(i,j,bi,bj) = 0. _d 0
88 ELSE
89 rH(i,j,bi,bj) = 1. _d 0 / h(i,j,bi,bj)
90 ENDIF
91 ENDDO
92 ENDDO
93 ENDDO
94 ENDDO
95 _EXCH_XY_R4( H, myThid )
96 _EXCH_XY_R4( rH, myThid )
97
98 C-- Now calculate "lopping" factors hFac.
99 zG = delZ(1)*0.5 D0
100 zFace(1) = 0
101 rDzC(1) = 2. _d 0/delZ(1)
102 DO K=1,Nz-1
103 saFac(K) = 1. D0
104 zC(K) = zG
105 zG = zG + (delZ(K)+delZ(K+1))*0.5 D0
106 zFace(K+1) = zFace(K)+delZ(K)
107 rDzC(K+1) = 2. _d 0/(delZ(K)+delZ(K+1))
108 ENDDO
109 zC(Nz) = zG
110 zFace(Nz+1) = zFace(Nz)+delZ(Nz)
111 DO K=1,Nz
112 zUpper(K) = zFace(K)
113 zLower(K) = zFace(K+1)
114 dzF(K) = delz(K)
115 rdzF(K) = 1.d0/dzF(K)
116 ENDDO
117 DO bj=myByLo(myThid), myByHi(myThid)
118 DO bi=myBxLo(myThid), myBxHi(myThid)
119 DO K=1, Nz
120 DO J=1,sNy
121 DO I=1,sNx
122 hFacC(I,J,K,bi,bj) = 1.
123 IF ( H(I,J,bi,bj) .LE. zUpper(K) ) THEN
124 C Below base of domain
125 hFacC(I,J,K,bi,bj) = 0.
126 ELSEIF ( H(I,J,bi,bj) .GT. zLower(K) ) THEN
127 C Base of domain is below this cell
128 hFacC(I,J,K,bi,bj) = 1.
129 ELSE
130 C Base of domain is in this cell
131 C Set hFac tp the fraction of the cell that is open.
132 phi = zUpper(K)-H(I,J,bi,bj)
133 hFacC(I,J,K,bi,bj) = phi/(zUpper(K)-zLower(K))
134 ENDIF
135 ENDDO
136 ENDDO
137 ENDDO
138 ENDDO
139 ENDDO
140 _EXCH_XYZ_R4(hFacC , myThid )
141
142 DO bj=myByLo(myThid), myByHi(myThid)
143 DO bi=myBxLo(myThid), myBxHi(myThid)
144 DO K=1, Nz
145 DO J=1,sNy
146 DO I=1,sNx
147 hFacW(I,J,K,bi,bj)=
148 & MIN(hFacC(I,J,K,bi,bj),hFacC(I-1,J,K,bi,bj))
149 hFacS(I,J,K,bi,bj)=
150 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,J-1,K,bi,bj))
151 ENDDO
152 ENDDO
153 ENDDO
154 ENDDO
155 ENDDO
156 _EXCH_XYZ_R4(hFacW , myThid )
157 _EXCH_XYZ_R4(hFacS , myThid )
158
159 C-- Calculate recipricols of hFacC, hFacW and hFacS
160 DO bj=myByLo(myThid), myByHi(myThid)
161 DO bi=myBxLo(myThid), myBxHi(myThid)
162 DO K=1, Nz
163 DO J=1,sNy
164 DO I=1,sNx
165 rhFacC(I,J,K,bi,bj)=0. D0
166 if (hFacC(I,J,K,bi,bj).ne.0.)
167 & rhFacC(I,J,K,bi,bj)=1. D0 /hFacC(I,J,K,bi,bj)
168 rhFacW(I,J,K,bi,bj)=0. D0
169 if (hFacW(I,J,K,bi,bj).ne.0.)
170 & rhFacW(I,J,K,bi,bj)=1. D0 /hFacW(I,J,K,bi,bj)
171 rhFacS(I,J,K,bi,bj)=0. D0
172 if (hFacS(I,J,K,bi,bj).ne.0.)
173 & rhFacS(I,J,K,bi,bj)=1. D0 /hFacS(I,J,K,bi,bj)
174 ENDDO
175 ENDDO
176 ENDDO
177 ENDDO
178 ENDDO
179 _EXCH_XYZ_R4(rhFacC , myThid )
180 _EXCH_XYZ_R4(rhFacW , myThid )
181 _EXCH_XYZ_R4(rhFacS , myThid )
182 C
183 RETURN
184 END

  ViewVC Help
Powered by ViewVC 1.1.22