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

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

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


Revision 1.10 - (show annotations) (download)
Thu May 28 16:19:50 1998 UTC (26 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint4
Changes since 1.9: +35 -11 lines
Changes to:
 o read in coefficients for POLY3 EOS.
 o find_rho() polynomial evaluation has been factorized.
 o additional density field needed in calc_iso_slopes() with non-linear EOS.

This EOS must use the appropriate version of KNUDSEN to generate the
coefficients file (POLY3.COEFFS). C7 and C8 were back to front in
all previous versions of the model (compare01).

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/dynamics.F,v 1.9 1998/05/25 21:29:45 cnh Exp $
2
3 #include "CPP_EEOPTIONS.h"
4
5 SUBROUTINE DYNAMICS(myTime, myIter, myThid)
6 C /==========================================================\
7 C | SUBROUTINE DYNAMICS |
8 C | o Controlling routine for the explicit part of the model |
9 C | dynamics. |
10 C |==========================================================|
11 C | This routine evaluates the "dynamics" terms for each |
12 C | block of ocean in turn. Because the blocks of ocean have |
13 C | overlap regions they are independent of one another. |
14 C | If terms involving lateral integrals are needed in this |
15 C | routine care will be needed. Similarly finite-difference |
16 C | operations with stencils wider than the overlap region |
17 C | require special consideration. |
18 C | Notes |
19 C | ===== |
20 C | C*P* comments indicating place holders for which code is |
21 C | presently being developed. |
22 C \==========================================================/
23
24 C == Global variables ===
25 #include "SIZE.h"
26 #include "EEPARAMS.h"
27 #include "CG2D.h"
28 #include "PARAMS.h"
29 #include "DYNVARS.h"
30
31 C == Routine arguments ==
32 C myTime - Current time in simulation
33 C myIter - Current iteration number in simulation
34 C myThid - Thread number for this instance of the routine.
35 INTEGER myThid
36 _RL myTime
37 INTEGER myIter
38
39 C == Local variables
40 C xA, yA - Per block temporaries holding face areas
41 C uTrans, vTrans, wTrans - Per block temporaries holding flow transport
42 C o uTrans: Zonal transport
43 C o vTrans: Meridional transport
44 C o wTrans: Vertical transport
45 C maskC,maskUp o maskC: land/water mask for tracer cells
46 C o maskUp: land/water mask for W points
47 C aTerm, xTerm, cTerm - Work arrays for holding separate terms in
48 C mTerm, pTerm, tendency equations.
49 C fZon, fMer, fVer[STUV] o aTerm: Advection term
50 C o xTerm: Mixing term
51 C o cTerm: Coriolis term
52 C o mTerm: Metric term
53 C o pTerm: Pressure term
54 C o fZon: Zonal flux term
55 C o fMer: Meridional flux term
56 C o fVer: Vertical flux term - note fVer
57 C is "pipelined" in the vertical
58 C so we need an fVer for each
59 C variable.
60 C iMin, iMax - Ranges and sub-block indices on which calculations
61 C jMin, jMax are applied.
62 C bi, bj
63 C k, kUp, kDown, kM1 - Index for layer above and below. kUp and kDown
64 C are switched with layer to be the appropriate index
65 C into fVerTerm
66 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73 _RL aTerm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 _RL xTerm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75 _RL cTerm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 _RL mTerm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77 _RL pTerm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 _RL fZon (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79 _RL fMer (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
81 _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
82 _RL fVerU (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
83 _RL fVerV (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
84 _RL pH (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
85 _RL rhokm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86 _RL rhokp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87 _RL rhotmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88 _RL pSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89 _RL pSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90 _RL K13 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
91 _RL K23 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
92 _RL K33 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
93 _RL KapGM (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94 INTEGER iMin, iMax
95 INTEGER jMin, jMax
96 INTEGER bi, bj
97 INTEGER i, j
98 INTEGER k, kM1, kUp, kDown
99
100 C-- Set up work arrays with valid (i.e. not NaN) values
101 C These inital values do not alter the numerical results. They
102 C just ensure that all memory references are to valid floating
103 C point numbers. This prevents spurious hardware signals due to
104 C uninitialised but inert locations.
105 DO j=1-OLy,sNy+OLy
106 DO i=1-OLx,sNx+OLx
107 xA(i,j) = 0. _d 0
108 yA(i,j) = 0. _d 0
109 uTrans(i,j) = 0. _d 0
110 vTrans(i,j) = 0. _d 0
111 aTerm(i,j) = 0. _d 0
112 xTerm(i,j) = 0. _d 0
113 cTerm(i,j) = 0. _d 0
114 mTerm(i,j) = 0. _d 0
115 pTerm(i,j) = 0. _d 0
116 fZon(i,j) = 0. _d 0
117 fMer(i,j) = 0. _d 0
118 DO K=1,nZ
119 pH (i,j,k) = 0. _d 0
120 K13(i,j,k) = 0. _d 0
121 K23(i,j,k) = 0. _d 0
122 K33(i,j,k) = 0. _d 0
123 ENDDO
124 rhokm1(i,j) = 0. _d 0
125 rhokp1(i,j) = 0. _d 0
126 rhotmp(i,j) = 0. _d 0
127 ENDDO
128 ENDDO
129
130 DO bj=myByLo(myThid),myByHi(myThid)
131 DO bi=myBxLo(myThid),myBxHi(myThid)
132
133 C-- Boundary condition on hydrostatic pressure is pH(z=0)=0
134 DO j=1-OLy,sNy+OLy
135 DO i=1-OLx,sNx+OLx
136 pH(i,j,1) = 0. _d 0
137 K13(i,j,1) = 0. _d 0
138 K23(i,j,1) = 0. _d 0
139 K33(i,j,1) = 0. _d 0
140 KapGM(i,j) = 0. _d 0
141 ENDDO
142 ENDDO
143
144 C-- Set up work arrays that need valid initial values
145 DO j=1-OLy,sNy+OLy
146 DO i=1-OLx,sNx+OLx
147 wTrans(i,j) = 0. _d 0
148 fVerT(i,j,1) = 0. _d 0
149 fVerT(i,j,2) = 0. _d 0
150 fVerS(i,j,1) = 0. _d 0
151 fVerS(i,j,2) = 0. _d 0
152 fVerU(i,j,1) = 0. _d 0
153 fVerU(i,j,2) = 0. _d 0
154 fVerV(i,j,1) = 0. _d 0
155 fVerV(i,j,2) = 0. _d 0
156 ENDDO
157 ENDDO
158
159 iMin = 1-OLx+1
160 iMax = sNx+OLx
161 jMin = 1-OLy+1
162 jMax = sNy+OLy
163
164 C-- Calculate gradient of surface pressure
165 CALL GRAD_PSURF(
166 I bi,bj,iMin,iMax,jMin,jMax,
167 O pSurfX,pSurfY,
168 I myThid)
169
170 C-- Update fields in top level according to tendency terms
171 CALL TIMESTEP(
172 I bi,bj,iMin,iMax,jMin,jMax,1,pSurfX,pSurfY,myThid)
173
174 C-- Density of 1st level (below W(1)) reference to level 1
175 CALL FIND_RHO(
176 I bi, bj, iMin, iMax, jMin, jMax, 1, 1, eosType,
177 O rhoKm1,
178 I myThid )
179 C-- Integrate hydrostatic balance for pH with BC of pH(z=0)=0
180 CALL CALC_PH(
181 I bi,bj,iMin,iMax,jMin,jMax,1,rhoKm1,rhoKm1,
182 U pH,
183 I myThid )
184 DO J=1-Oly,sNy+Oly
185 DO I=1-Olx,sNx+Olx
186 rhoKp1(I,J)=rhoKm1(I,J)
187 ENDDO
188 ENDDO
189
190 DO K=2,Nz
191 C-- Update fields in Kth level according to tendency terms
192 CALL TIMESTEP(
193 I bi,bj,iMin,iMax,jMin,jMax,K,pSurfX,pSurfY,myThid)
194 C-- Density of K-1 level (above W(K)) reference to K-1 level
195 copt CALL FIND_RHO(
196 copt I bi, bj, iMin, iMax, jMin, jMax, K-1, K-1, eosType,
197 copt O rhoKm1,
198 copt I myThid )
199 C rhoKm1=rhoKp1
200 DO J=1-Oly,sNy+Oly
201 DO I=1-Olx,sNx+Olx
202 rhoKm1(I,J)=rhoKp1(I,J)
203 ENDDO
204 ENDDO
205 C-- Density of K level (below W(K)) reference to K level
206 CALL FIND_RHO(
207 I bi, bj, iMin, iMax, jMin, jMax, K, K, eosType,
208 O rhoKp1,
209 I myThid )
210 C-- Density of K-1 level (above W(K)) reference to K level
211 CALL FIND_RHO(
212 I bi, bj, iMin, iMax, jMin, jMax, K-1, K, eosType,
213 O rhotmp,
214 I myThid )
215 C-- Calculate iso-neutral slopes for the GM/Redi parameterisation
216 CALL CALC_ISOSLOPES(
217 I bi, bj, iMin, iMax, jMin, jMax, K,
218 I rhoKm1, rhoKp1, rhotmp,
219 O K13, K23, K33, KapGM,
220 I myThid )
221 C-- Calculate static stability and mix where convectively unstable
222 CALL CONVECT(
223 I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoKp1,
224 I myTime,myIter,myThid)
225 C-- Density of K-1 level (above W(K)) reference to K-1 level
226 CALL FIND_RHO(
227 I bi, bj, iMin, iMax, jMin, jMax, K-1, K-1, eosType,
228 O rhoKm1,
229 I myThid )
230 C-- Density of K level (below W(K)) referenced to K level
231 CALL FIND_RHO(
232 I bi, bj, iMin, iMax, jMin, jMax, K, K, eosType,
233 O rhoKp1,
234 I myThid )
235 C-- Integrate hydrostatic balance for pH with BC of pH(z=0)=0
236 CALL CALC_PH(
237 I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoKp1,
238 U pH,
239 I myThid )
240
241 ENDDO
242
243 DO K = Nz, 1, -1
244 kM1 =max(1,k-1) ! Points to level above k (=k-1)
245 kUp =1+MOD(k+1,2) ! Cycles through 1,2 to point to layer above
246 kDown=1+MOD(k,2) ! Cycles through 2,1 to point to current layer
247 iMin = 1-OLx+2
248 iMax = sNx+OLx-1
249 jMin = 1-OLy+2
250 jMax = sNy+OLy-1
251
252 C-- Get temporary terms used by tendency routines
253 CALL CALC_COMMON_FACTORS (
254 I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
255 O xA,yA,uTrans,vTrans,wTrans,maskC,maskUp,
256 I myThid)
257
258 C-- Calculate accelerations in the momentum equations
259 IF ( momStepping ) THEN
260 CALL CALC_MOM_RHS(
261 I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
262 I xA,yA,uTrans,vTrans,wTrans,maskC,
263 I pH,
264 U aTerm,xTerm,cTerm,mTerm,pTerm,
265 U fZon, fMer, fVerU, fVerV,
266 I myThid)
267 ENDIF
268
269 C-- Calculate active tracer tendencies
270 IF ( tempStepping ) THEN
271 CALL CALC_GT(
272 I bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,
273 I xA,yA,uTrans,vTrans,wTrans,maskUp,
274 I K13,K23,K33,KapGM,
275 U aTerm,xTerm,fZon,fMer,fVerT,
276 I myThid)
277 ENDIF
278 Cdbg CALL CALC_GS(
279 Cdbg I bi,bj,iMin,iMax,jMin,jMax, k,kM1,kUp,kDown,
280 Cdbg I xA,yA,uTrans,vTrans,wTrans,maskUp,
281 Cdbg I K13,K23,K33,KapGM,
282 Cdbg U aTerm,xTerm,fZon,fMer,fVerS,
283 Cdbg I myThid)
284
285 ENDDO
286
287 ENDDO
288 ENDDO
289
290 !dbg write(0,*) 'dynamics: pS',minval(cg2d_x),maxval(cg2d_x)
291 !dbg write(0,*) 'dynamics: U',minval(uVel(1:sNx,1:sNy,:,:,:)),
292 !dbg & maxval(uVel(1:sNx,1:sNy,:,:,:))
293 !dbg write(0,*) 'dynamics: V',minval(vVel(1:sNx,1:sNy,:,:,:)),
294 !dbg & maxval(vVel(1:sNx,1:sNy,:,:,:))
295 !dbg write(0,*) 'dynamics: K13',minval(K13(1:sNx,1:sNy,:)),
296 !dbg & maxval(K13(1:sNx,1:sNy,:))
297 !dbg write(0,*) 'dynamics: K23',minval(K23(1:sNx,1:sNy,:)),
298 !dbg & maxval(K23(1:sNx,1:sNy,:))
299 !dbg write(0,*) 'dynamics: K33',minval(K33(1:sNx,1:sNy,:)),
300 !dbg & maxval(K33(1:sNx,1:sNy,:))
301 !dbg write(0,*) 'dynamics: gT',minval(gT(1:sNx,1:sNy,:,:,:)),
302 !dbg & maxval(gT(1:sNx,1:sNy,:,:,:))
303 !dbg write(0,*) 'dynamics: T',minval(Theta(1:sNx,1:sNy,:,:,:)),
304 !dbg & maxval(Theta(1:sNx,1:sNy,:,:,:))
305 !dbg write(0,*) 'dynamics: pH',minval(pH/(Gravity*Rhonil)),
306 !dbg & maxval(pH/(Gravity*Rhonil))
307
308 RETURN
309 END

  ViewVC Help
Powered by ViewVC 1.1.22