/[MITgcm]/MITgcm/verification/global_ocean_pressure/code/calc_phi_hyd.F
ViewVC logotype

Contents of /MITgcm/verification/global_ocean_pressure/code/calc_phi_hyd.F

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


Revision 1.3 - (show annotations) (download)
Sat Feb 8 02:26:34 2003 UTC (21 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +1 -1 lines
FILE REMOVED
o find difficult to maintain the local version of dynamics.F up to date.
  therefore, has been remove from the code directory.
  One can recover the same version (but up to date) simply
  by activating the commented lines [between lines Cml( and Cml) ],
  at the end of the standard version of dynamics.F
o finite volume form of calc_phi_hyd.F is now a standard option.
  only needs to set integr_GeoPot=1 in file "data" to select this form.

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

  ViewVC Help
Powered by ViewVC 1.1.22