/[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.4 - (show annotations) (download)
Tue Jun 9 16:48:02 1998 UTC (26 years ago) by cnh
Branch: MAIN
Changes since 1.3: +34 -29 lines
Changes to support topography, hydrography and
forcing from files

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_depths.F,v 1.3 1998/06/08 21:43:01 cnh Exp $
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 _BARRIER
53 IF ( bathyFile .EQ. ' ' ) THEN
54 C Set up a flat bottom box with doubly periodic topology.
55 C H is the basic variable from which other terms are derived. It
56 C is the term that would be set from an external file for a
57 C realistic problem.
58 phi = 0. D0
59 DO K=1,Nz
60 phi = phi+delZ(K)
61 ENDDO
62 DO bj = myByLo(myThid), myByHi(myThid)
63 DO bi = myBxLo(myThid), myBxHi(myThid)
64 DO j=1,sNy
65 DO i=1,sNx
66 iG = myXGlobalLo-1+(bi-1)*sNx+I
67 jG = myYGlobalLo-1+(bj-1)*sNy+J
68 C Default depth of full domain
69 H(i,j,bi,bj) = phi
70 C Test for eastern edge
71 IF ( iG .EQ. nX ) H(i,j,bi,bj) = 0.
72 C Test for northern edge
73 IF ( jG .EQ. nY ) H(i,j,bi,bj) = 0.
74 C Island
75 IF ( iG .EQ. 1 .AND.
76 & jG .EQ. 24 ) H(i,j,bi,bj) = 0.75*phi
77 ENDDO
78 ENDDO
79 ENDDO
80 ENDDO
81 ELSE
82 _BEGIN_MASTER( myThid )
83 CALL READ_FLD_XY_RS( bathyFile, ' ', H, 0, myThid )
84 _END_MASTER(myThid)
85 ENDIF
86 _EXCH_XY_R4( H, myThid )
87
88 C-- Cacluate quantities derived from XY depth map
89 DO bj = myByLo(myThid), myByHi(myThid)
90 DO bi = myBxLo(myThid), myBxHi(myThid)
91 DO J=1,sNy
92 DO I=1,sNx
93 C Inverse of depth
94 IF ( h(i,j,bi,bj) .EQ. 0. _d 0 ) THEN
95 rH(i,j,bi,bj) = 0. _d 0
96 ELSE
97 rH(i,j,bi,bj) = 1. _d 0 / h(i,j,bi,bj)
98 ENDIF
99 ENDDO
100 ENDDO
101 ENDDO
102 ENDDO
103 _EXCH_XY_R4( rH, myThid )
104
105 C-- Now calculate "lopping" factors hFac.
106 zG = delZ(1)*0.5 D0
107 zFace(1) = 0
108 rDzC(1) = 2. _d 0/delZ(1)
109 DO K=1,Nz-1
110 saFac(K) = 1. D0
111 zC(K) = zG
112 zG = zG + (delZ(K)+delZ(K+1))*0.5 D0
113 zFace(K+1) = zFace(K)+delZ(K)
114 rDzC(K+1) = 2. _d 0/(delZ(K)+delZ(K+1))
115 ENDDO
116 zC(Nz) = zG
117 zFace(Nz+1) = zFace(Nz)+delZ(Nz)
118 DO K=1,Nz
119 zUpper(K) = zFace(K)
120 zLower(K) = zFace(K+1)
121 dzF(K) = delz(K)
122 rdzF(K) = 1.d0/dzF(K)
123 ENDDO
124 DO bj=myByLo(myThid), myByHi(myThid)
125 DO bi=myBxLo(myThid), myBxHi(myThid)
126 DO K=1, Nz
127 DO J=1,sNy
128 DO I=1,sNx
129 hFacC(I,J,K,bi,bj) = 1.
130 IF ( H(I,J,bi,bj) .LE. zUpper(K) ) THEN
131 C Below base of domain
132 hFacC(I,J,K,bi,bj) = 0.
133 ELSEIF ( H(I,J,bi,bj) .GT. zLower(K) ) THEN
134 C Base of domain is below this cell
135 hFacC(I,J,K,bi,bj) = 1.
136 ELSE
137 C Base of domain is in this cell
138 C Set hFac tp the fraction of the cell that is open.
139 phi = zUpper(K)-H(I,J,bi,bj)
140 hFacC(I,J,K,bi,bj) = phi/(zUpper(K)-zLower(K))
141 ENDIF
142 ENDDO
143 ENDDO
144 ENDDO
145 ENDDO
146 ENDDO
147 _EXCH_XYZ_R4(hFacC , myThid )
148
149 DO bj=myByLo(myThid), myByHi(myThid)
150 DO bi=myBxLo(myThid), myBxHi(myThid)
151 DO K=1, Nz
152 DO J=1,sNy
153 DO I=1,sNx
154 hFacW(I,J,K,bi,bj)=
155 & MIN(hFacC(I,J,K,bi,bj),hFacC(I-1,J,K,bi,bj))
156 hFacS(I,J,K,bi,bj)=
157 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,J-1,K,bi,bj))
158 ENDDO
159 ENDDO
160 ENDDO
161 ENDDO
162 ENDDO
163 _EXCH_XYZ_R4(hFacW , myThid )
164 _EXCH_XYZ_R4(hFacS , myThid )
165
166 C-- Calculate recipricols of hFacC, hFacW and hFacS
167 DO bj=myByLo(myThid), myByHi(myThid)
168 DO bi=myBxLo(myThid), myBxHi(myThid)
169 DO K=1, Nz
170 DO J=1,sNy
171 DO I=1,sNx
172 rhFacC(I,J,K,bi,bj)=0. D0
173 if (hFacC(I,J,K,bi,bj).ne.0.)
174 & rhFacC(I,J,K,bi,bj)=1. D0 /hFacC(I,J,K,bi,bj)
175 rhFacW(I,J,K,bi,bj)=0. D0
176 if (hFacW(I,J,K,bi,bj).ne.0.)
177 & rhFacW(I,J,K,bi,bj)=1. D0 /hFacW(I,J,K,bi,bj)
178 rhFacS(I,J,K,bi,bj)=0. D0
179 if (hFacS(I,J,K,bi,bj).ne.0.)
180 & rhFacS(I,J,K,bi,bj)=1. D0 /hFacS(I,J,K,bi,bj)
181 ENDDO
182 ENDDO
183 ENDDO
184 ENDDO
185 ENDDO
186 _EXCH_XYZ_R4(rhFacC , myThid )
187 _EXCH_XYZ_R4(rhFacW , myThid )
188 _EXCH_XYZ_R4(rhFacS , myThid )
189 C
190 RETURN
191 END

  ViewVC Help
Powered by ViewVC 1.1.22