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

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

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


Revision 1.25 - (show annotations) (download)
Sat Feb 8 02:09:20 2003 UTC (21 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint48d_pre
Changes since 1.24: +123 -76 lines
in preparation for r*:
 new S/R (calc_grad_phi_hyd.F) to compute Hydrostatic potential gradient.
 pass the 2 comp. of the grad. as arguments to momentum S/R.
for the moment, only used if it does not change the results.

1 C $Header: /u/gcmpack/MITgcm/model/src/calc_phi_hyd.F,v 1.24 2002/12/10 02:55:47 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: CALC_PHI_HYD
8 C !INTERFACE:
9 SUBROUTINE CALC_PHI_HYD(
10 I bi, bj, iMin, iMax, jMin, jMax, K,
11 I tFld, sFld,
12 U phiHyd,
13 O dPhiHydX, dPhiHydY,
14 I myTime, myIter, myThid)
15 C !DESCRIPTION: \bv
16 C *==========================================================*
17 C | SUBROUTINE CALC_PHI_HYD |
18 C | o Integrate the hydrostatic relation to find the Hydros. |
19 C *==========================================================*
20 C | Potential (ocean: Pressure/rho ; atmos = geopotential)|
21 C | On entry: |
22 C | tFld,sFld are the current thermodynamics quantities|
23 C | (unchanged on exit) |
24 C | phiHyd(i,j,1:k-1) is the hydrostatic Potential |
25 C | at cell centers (tracer points) |
26 C | - 1:k-1 layers are valid |
27 C | - k:Nr layers are invalid |
28 C | phiHyd(i,j,k) is the hydrostatic Potential |
29 C | (ocean only_^) at cell the interface k (w point above) |
30 C | On exit: |
31 C | phiHyd(i,j,1:k) is the hydrostatic Potential |
32 C | at cell centers (tracer points) |
33 C | - 1:k layers are valid |
34 C | - k+1:Nr layers are invalid |
35 C | phiHyd(i,j,k+1) is the hydrostatic Potential (P/rho) |
36 C | (ocean only-^) at cell the interface k+1 (w point below)|
37 C | Atmosphere: |
38 C | integr_GeoPot allows to select one integration method |
39 C | (see the list below) |
40 C *==========================================================*
41 C \ev
42 C !USES:
43 IMPLICIT NONE
44 C == Global variables ==
45 #include "SIZE.h"
46 #include "GRID.h"
47 #include "EEPARAMS.h"
48 #include "PARAMS.h"
49 c #include "FFIELDS.h"
50 #ifdef ALLOW_AUTODIFF_TAMC
51 #include "tamc.h"
52 #include "tamc_keys.h"
53 #endif /* ALLOW_AUTODIFF_TAMC */
54 #include "SURFACE.h"
55 #include "DYNVARS.h"
56
57 C !INPUT/OUTPUT PARAMETERS:
58 C == Routine arguments ==
59 INTEGER bi,bj,iMin,iMax,jMin,jMax,K
60 _RL tFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
61 _RL sFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
62 _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
63 _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
64 _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
65 _RL myTime
66 INTEGER myIter, myThid
67
68 #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
69
70 C !LOCAL VARIABLES:
71 C == Local variables ==
72 INTEGER i,j, Kp1
73 _RL zero, one, half
74 _RL alphaRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75 _RL dRloc,dRlocKp1,locAlpha
76 _RL ddPI, ddPIm, ddPIp, ratioRp, ratioRm
77 INTEGER iMnLoc,jMnLoc
78 PARAMETER ( zero= 0. _d 0 , one= 1. _d 0 , half= .5 _d 0 )
79 CEOP
80
81 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
82 C Atmosphere:
83 C integr_GeoPot => select one option for the integration of the Geopotential:
84 C = 0 : Energy Conserving Form, No hFac ;
85 C = 1 : Finite Volume Form, with hFac, linear in P by Half level;
86 C =2,3: Finite Difference Form, with hFac, linear in P between 2 Tracer levels
87 C 2 : case Tracer level at the middle of InterFace_W;
88 C 3 : case InterFace_W at the middle of Tracer levels;
89 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
90
91 #ifdef ALLOW_AUTODIFF_TAMC
92 act1 = bi - myBxLo(myThid)
93 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
94
95 act2 = bj - myByLo(myThid)
96 max2 = myByHi(myThid) - myByLo(myThid) + 1
97
98 act3 = myThid - 1
99 max3 = nTx*nTy
100
101 act4 = ikey_dynamics - 1
102
103 ikey = (act1 + 1) + act2*max1
104 & + act3*max1*max2
105 & + act4*max1*max2*max3
106 #endif /* ALLOW_AUTODIFF_TAMC */
107
108
109 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
110 IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
111 C This is the hydrostatic pressure calculation for the Ocean
112 C which uses the FIND_RHO() routine to calculate density
113 C before integrating g*rho over the current layer/interface
114 #ifdef ALLOW_AUTODIFF_TAMC
115 CADJ GENERAL
116 #endif /* ALLOW_AUTODIFF_TAMC */
117
118 dRloc=drC(k)
119 IF (k.EQ.1) dRloc=drF(1)
120 IF (k.EQ.Nr) THEN
121 dRlocKp1=0.
122 ELSE
123 dRlocKp1=drC(k+1)
124 ENDIF
125
126 C-- If this is the top layer we impose the boundary condition
127 C P(z=eta) = P(atmospheric_loading)
128 IF (k.EQ.1) THEN
129 DO j=jMin,jMax
130 DO i=iMin,iMax
131 phiHyd(i,j,k) = phi0surf(i,j,bi,bj)
132 c phiHyd(i,j,k) = 0.
133 ENDDO
134 ENDDO
135 ENDIF
136
137 C Calculate density
138 #ifdef ALLOW_AUTODIFF_TAMC
139 kkey = (ikey-1)*Nr + k
140 CADJ STORE tFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
141 CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
142 #endif /* ALLOW_AUTODIFF_TAMC */
143 CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k,
144 & tFld, sFld,
145 & alphaRho, myThid)
146
147 C Quasi-hydrostatic terms are added in as if they modify the buoyancy
148 IF (quasiHydrostatic) THEN
149 CALL QUASIHYDROSTATICTERMS(bi,bj,k,alphaRho,myThid)
150 ENDIF
151
152 C--- Hydrostatic pressure at cell centers
153
154 IF (integr_GeoPot.EQ.1) THEN
155 C -- Finite Volume Form
156
157 DO j=jMin,jMax
158 DO i=iMin,iMax
159
160 C---------- This discretization is the "finite volume" form
161 C which has not been used to date since it does not
162 C conserve KE+PE exactly even though it is more natural
163 C
164 IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
165 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
166 & + hFacC(i,j,k,bi,bj)
167 & *drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
168 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
169 ENDIF
170 IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)
171 & + drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
172 phiHyd(i,j,k)=phiHyd(i,j,k)+
173 & + half*drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
174
175 ENDDO
176 ENDDO
177
178 ELSE
179 C -- Finite Difference Form
180
181 DO j=jMin,jMax
182 DO i=iMin,iMax
183
184 C---------- This discretization is the "energy conserving" form
185 C which has been used since at least Adcroft et al., MWR 1997
186 C
187
188 phiHyd(i,j,k)=phiHyd(i,j,k)
189 & +half*dRloc*gravity*alphaRho(i,j)*recip_rhoConst
190 IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)
191 & +half*dRlocKp1*gravity*alphaRho(i,j)*recip_rhoConst
192
193 C---------- Compute bottom pressure deviation from gravity*rho0*H
194 C This has to be done starting from phiHyd at the current
195 C tracer point and .5 of the cell's thickness has to be
196 C substracted from hFacC
197 IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
198 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
199 & + (hFacC(i,j,k,bi,bj)-half)*drF(K)
200 & *gravity*alphaRho(i,j)*recip_rhoConst
201 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
202 ENDIF
203
204 ENDDO
205 ENDDO
206
207 C -- end if integr_GeoPot = ...
208 ENDIF
209
210 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
211 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
212 C This is the hydrostatic pressure calculation for the Ocean
213 C which uses the FIND_RHO() routine to calculate density
214 C before integrating (1/rho)'*dp over the current layer/interface
215 #ifdef ALLOW_AUTODIFF_TAMC
216 CADJ GENERAL
217 #endif /* ALLOW_AUTODIFF_TAMC */
218
219 dRloc=drC(k)
220 IF (k.EQ.1) dRloc=drF(1)
221 IF (k.EQ.Nr) THEN
222 dRlocKp1=0.
223 ELSE
224 dRlocKp1=drC(k+1)
225 ENDIF
226
227 IF (k.EQ.1) THEN
228 DO j=jMin,jMax
229 DO i=iMin,iMax
230 phiHyd(i,j,k) = phi0surf(i,j,bi,bj)
231 c phiHyd(i,j,k) = 0.
232 ENDDO
233 ENDDO
234 ENDIF
235
236 C Calculate density
237 #ifdef ALLOW_AUTODIFF_TAMC
238 kkey = (ikey-1)*Nr + k
239 CADJ STORE tFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
240 CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
241 #endif /* ALLOW_AUTODIFF_TAMC */
242 CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k,
243 & tFld, sFld,
244 & alphaRho, myThid)
245 #ifdef ALLOW_AUTODIFF_TAMC
246 CADJ STORE alphaRho (:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
247 #endif /* ALLOW_AUTODIFF_TAMC */
248
249
250 C---- Hydrostatic pressure at cell centers
251
252 IF (integr_GeoPot.EQ.1) THEN
253 C -- Finite Volume Form
254
255 DO j=jMin,jMax
256 DO i=iMin,iMax
257 locAlpha=alphaRho(i,j)+rhoConst
258 locAlpha=maskC(i,j,k,bi,bj)*
259 & (one/locAlpha - recip_rhoConst)
260 c IF (locAlpha.NE.0.) locAlpha=maskC(i,j,k,bi,bj)/locAlpha
261
262 C---------- This discretization is the "finite volume" form
263 C which has not been used to date since it does not
264 C conserve KE+PE exactly even though it is more natural
265 C
266 IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
267 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
268 & + hFacC(i,j,k,bi,bj)*drF(K)*locAlpha
269 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
270 ENDIF
271 IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)
272 & + hFacC(i,j,k,bi,bj)*drF(K)*locAlpha
273 phiHyd(i,j,k)=phiHyd(i,j,k)
274 & +(hFacC(i,j,k,bi,bj)-half)*drF(K)*locAlpha
275
276 ENDDO
277 ENDDO
278
279 ELSE
280 C -- Finite Difference Form
281
282 DO j=jMin,jMax
283 DO i=iMin,iMax
284 locAlpha=alphaRho(i,j)+rhoConst
285 locAlpha=maskC(i,j,k,bi,bj)*
286 & (one/locAlpha - recip_rhoConst)
287 c IF (locAlpha.NE.0.) locAlpha=maskC(i,j,k,bi,bj)/locAlpha
288
289 C---------- This discretization is the "energy conserving" form
290
291 phiHyd(i,j,k)=phiHyd(i,j,k)
292 & + half*dRloc*locAlpha
293 IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)
294 & + half*dRlocKp1*locAlpha
295
296
297 C---------- Compute gravity*(sea surface elevation) first
298 C This has to be done starting from phiHyd at the current
299 C tracer point and .5 of the cell's thickness has to be
300 C substracted from hFacC
301 IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
302 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
303 & + (hFacC(i,j,k,bi,bj)-half)*drF(k)*locAlpha
304 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
305 ENDIF
306
307 ENDDO
308 ENDDO
309
310 C -- end if integr_GeoPot = ...
311 ENDIF
312
313 ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
314 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
315 C This is the hydrostatic geopotential calculation for the Atmosphere
316 C The ideal gas law is used implicitly here rather than calculating
317 C the specific volume, analogous to the oceanic case.
318
319 C Integrate d Phi / d pi
320
321 IF (integr_GeoPot.EQ.0) THEN
322 C -- Energy Conserving Form, No hFac --
323 C------------ The integration for the first level phi(k=1) is the same
324 C for both the "finite volume" and energy conserving methods.
325 Ci *NOTE* o Working with geopotential Anomaly, the geopotential boundary
326 C condition is simply Phi-prime(Ro_surf)=0.
327 C o convention ddPI > 0 (same as drF & drC)
328 C-----------------------------------------------------------------------
329 IF (K.EQ.1) THEN
330 ddPIp=atm_Cp*( ((rF(K)/atm_Po)**atm_kappa)
331 & -((rC(K)/atm_Po)**atm_kappa) )
332 DO j=jMin,jMax
333 DO i=iMin,iMax
334 c phiHyd(i,j,K)=
335 phiHyd(i,j,K)= phi0surf(i,j,bi,bj)+
336 & ddPIp*maskC(i,j,K,bi,bj)
337 & *(tFld(I,J,K,bi,bj)-tRef(K))
338 ENDDO
339 ENDDO
340 ELSE
341 C-------- This discretization is the energy conserving form
342 ddPI=atm_Cp*( ((rC(K-1)/atm_Po)**atm_kappa)
343 & -((rC( K )/atm_Po)**atm_kappa) )*0.5
344 DO j=jMin,jMax
345 DO i=iMin,iMax
346 phiHyd(i,j,K)=phiHyd(i,j,K-1)
347 & +ddPI*maskC(i,j,K-1,bi,bj)
348 & *(tFld(I,J,K-1,bi,bj)-tRef(K-1))
349 & +ddPI*maskC(i,j, K ,bi,bj)
350 & *(tFld(I,J, K ,bi,bj)-tRef( K ))
351 C Old code (atmos-exact) looked like this
352 Cold phiHyd(i,j,K)=phiHyd(i,j,K-1) - ddPI*
353 Cold & (tFld(I,J,K-1,bi,bj)+tFld(I,J,K,bi,bj)-2.*tRef(K))
354 ENDDO
355 ENDDO
356 ENDIF
357 C end: Energy Conserving Form, No hFac --
358 C-----------------------------------------------------------------------
359
360 ELSEIF (integr_GeoPot.EQ.1) THEN
361 C -- Finite Volume Form, with hFac, linear in P by Half level --
362 C---------
363 C Finite Volume formulation consistent with Partial Cell, linear in p by piece
364 C Note: a true Finite Volume form should be linear between 2 Interf_W :
365 C phi_C = (phi_W_k+ phi_W_k+1)/2 ; but not accurate in Stratosphere (low p)
366 C also: if Interface_W at the middle between tracer levels, this form
367 C is close to the Energy Cons. form in the Interior, except for the
368 C non-linearity in PI(p)
369 C---------
370 IF (K.EQ.1) THEN
371 ddPIp=atm_Cp*( ((rF(K)/atm_Po)**atm_kappa)
372 & -((rC(K)/atm_Po)**atm_kappa) )
373 DO j=jMin,jMax
374 DO i=iMin,iMax
375 c phiHyd(i,j,K)=
376 phiHyd(i,j,K)= phi0surf(i,j,bi,bj)+
377 & ddPIp*_hFacC(I,J, K ,bi,bj)
378 & *(tFld(I,J, K ,bi,bj)-tRef( K ))
379 ENDDO
380 ENDDO
381 ELSE
382 ddPIm=atm_Cp*( ((rC(K-1)/atm_Po)**atm_kappa)
383 & -((rF( K )/atm_Po)**atm_kappa) )
384 ddPIp=atm_Cp*( ((rF( K )/atm_Po)**atm_kappa)
385 & -((rC( K )/atm_Po)**atm_kappa) )
386 DO j=jMin,jMax
387 DO i=iMin,iMax
388 phiHyd(i,j,K) = phiHyd(i,j,K-1)
389 & +ddPIm*_hFacC(I,J,K-1,bi,bj)
390 & *(tFld(I,J,K-1,bi,bj)-tRef(K-1))
391 & +ddPIp*_hFacC(I,J, K ,bi,bj)
392 & *(tFld(I,J, K ,bi,bj)-tRef( K ))
393 ENDDO
394 ENDDO
395 ENDIF
396 C end: Finite Volume Form, with hFac, linear in P by Half level --
397 C-----------------------------------------------------------------------
398
399 ELSEIF (integr_GeoPot.EQ.2) THEN
400 C -- Finite Difference Form, with hFac, Tracer Lev. = middle --
401 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
402 C Finite Difference formulation consistent with Partial Cell,
403 C case Tracer level at the middle of InterFace_W
404 C linear between 2 Tracer levels ; conserve energy in the Interior
405 C---------
406 Kp1 = min(Nr,K+1)
407 IF (K.EQ.1) THEN
408 ddPIm=atm_Cp*( ((rF( K )/atm_Po)**atm_kappa)
409 & -((rC( K )/atm_Po)**atm_kappa) ) * 2. _d 0
410 ddPIp=atm_Cp*( ((rC( K )/atm_Po)**atm_kappa)
411 & -((rC(Kp1)/atm_Po)**atm_kappa) )
412 DO j=jMin,jMax
413 DO i=iMin,iMax
414 c phiHyd(i,j,K)=
415 phiHyd(i,j,K)= phi0surf(i,j,bi,bj)+
416 & ( ddPIm*max(zero, _hFacC(i,j,K,bi,bj)-half)
417 & +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)-half) )
418 & *(tFld(i,j, K ,bi,bj)-tRef( K ))
419 & * maskC(i,j, K ,bi,bj)
420 ENDDO
421 ENDDO
422 ELSE
423 ddPIm=atm_Cp*( ((rC(K-1)/atm_Po)**atm_kappa)
424 & -((rC( K )/atm_Po)**atm_kappa) )
425 ddPIp=atm_Cp*( ((rC( K )/atm_Po)**atm_kappa)
426 & -((rC(Kp1)/atm_Po)**atm_kappa) )
427 DO j=jMin,jMax
428 DO i=iMin,iMax
429 phiHyd(i,j,K) = phiHyd(i,j,K-1)
430 & + ddPIm*0.5
431 & *(tFld(i,j,K-1,bi,bj)-tRef(K-1))
432 & * maskC(i,j,K-1,bi,bj)
433 & +(ddPIm*max(zero, _hFacC(i,j,K,bi,bj)-half)
434 & +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)-half) )
435 & *(tFld(i,j, K ,bi,bj)-tRef( K ))
436 & * maskC(i,j, K ,bi,bj)
437 ENDDO
438 ENDDO
439 ENDIF
440 C end: Finite Difference Form, with hFac, Tracer Lev. = middle --
441 C-----------------------------------------------------------------------
442
443 ELSEIF (integr_GeoPot.EQ.3) THEN
444 C -- Finite Difference Form, with hFac, Interface_W = middle --
445 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
446 C Finite Difference formulation consistent with Partial Cell,
447 C Valid & accurate if Interface_W at middle between tracer levels
448 C linear in p between 2 Tracer levels ; conserve energy in the Interior
449 C---------
450 Kp1 = min(Nr,K+1)
451 IF (K.EQ.1) THEN
452 ratioRm=0.5*drF(K)/(rF(k)-rC(K))
453 ratioRp=drF(K)*recip_drC(Kp1)
454 ddPIm=atm_Cp*( ((rF( K )/atm_Po)**atm_kappa)
455 & -((rC( K )/atm_Po)**atm_kappa) ) * 2. _d 0
456 ddPIp=atm_Cp*( ((rC( K )/atm_Po)**atm_kappa)
457 & -((rC(Kp1)/atm_Po)**atm_kappa) )
458 DO j=jMin,jMax
459 DO i=iMin,iMax
460 c phiHyd(i,j,K)=
461 phiHyd(i,j,K)= phi0surf(i,j,bi,bj)+
462 & ( ddPIm*max(zero,(_hFacC(i,j,K,bi,bj)-one)*ratioRm+half)
463 & +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)*ratioRp -half) )
464 & *(tFld(i,j, K ,bi,bj)-tRef( K ))
465 & * maskC(i,j, K ,bi,bj)
466 ENDDO
467 ENDDO
468 ELSE
469 ratioRm=drF(K)*recip_drC(K)
470 ratioRp=drF(K)*recip_drC(Kp1)
471 ddPIm=atm_Cp*( ((rC(K-1)/atm_Po)**atm_kappa)
472 & -((rC( K )/atm_Po)**atm_kappa) )
473 ddPIp=atm_Cp*( ((rC( K )/atm_Po)**atm_kappa)
474 & -((rC(Kp1)/atm_Po)**atm_kappa) )
475 DO j=jMin,jMax
476 DO i=iMin,iMax
477 phiHyd(i,j,K) = phiHyd(i,j,K-1)
478 & + ddPIm*0.5
479 & *(tFld(i,j,K-1,bi,bj)-tRef(K-1))
480 & * maskC(i,j,K-1,bi,bj)
481 & +(ddPIm*max(zero,(_hFacC(i,j,K,bi,bj)-one)*ratioRm+half)
482 & +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)*ratioRp -half) )
483 & *(tFld(i,j, K ,bi,bj)-tRef( K ))
484 & * maskC(i,j, K ,bi,bj)
485 ENDDO
486 ENDDO
487 ENDIF
488 C end: Finite Difference Form, with hFac, Interface_W = middle --
489 C-----------------------------------------------------------------------
490
491 ELSE
492 STOP 'CALC_PHI_HYD: Bad integr_GeoPot option !'
493 ENDIF
494
495 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
496 ELSE
497 STOP 'CALC_PHI_HYD: Bad value of buoyancyRelation !'
498 ENDIF
499
500 IF (momPressureForcing) THEN
501 iMnLoc = MAX(1-Olx+1,iMin)
502 jMnLoc = MAX(1-Oly+1,jMin)
503 CALL CALC_GRAD_PHI_HYD(
504 I k, bi, bj, iMnLoc,iMax, jMnLoc,jMax,
505 I phiHyd, alphaRho, tFld, sFld,
506 O dPhiHydX, dPhiHydY,
507 I myTime, myIter, myThid)
508 ENDIF
509
510 #endif /* INCLUDE_PHIHYD_CALCULATION_CODE */
511
512 RETURN
513 END

  ViewVC Help
Powered by ViewVC 1.1.22