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

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

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

revision 1.14 by jmc, Fri Jul 6 21:47:00 2001 UTC revision 1.21 by mlosch, Wed Sep 25 19:36:50 2002 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6    CBOP
7    C     !ROUTINE: CALC_PHI_HYD
8    C     !INTERFACE:
9        SUBROUTINE CALC_PHI_HYD(        SUBROUTINE CALC_PHI_HYD(
10       I                         bi, bj, iMin, iMax, jMin, jMax, K,       I                         bi, bj, iMin, iMax, jMin, jMax, K,
11       I                         theta, salt,       I                         tFld, sFld,
12       U                         phiHyd,       U                         phiHyd,
13       I                         myThid)       I                         myThid)
14  C     /==========================================================\  C     !DESCRIPTION: \bv
15    C     *==========================================================*
16  C     | SUBROUTINE CALC_PHI_HYD                                  |  C     | SUBROUTINE CALC_PHI_HYD                                  |
17  C     | o Integrate the hydrostatic relation to find the Hydros. |  C     | o Integrate the hydrostatic relation to find the Hydros. |
18    C     *==========================================================*
19  C     |    Potential (ocean: Pressure/rho ; atmos = geopotential)|  C     |    Potential (ocean: Pressure/rho ; atmos = geopotential)|
20  C     | On entry:                                                |  C     | On entry:                                                |
21  C     |   theta,salt    are the current thermodynamics quantities|  C     |   tFld,sFld     are the current thermodynamics quantities|
22  C     |                 (unchanged on exit)                      |  C     |                 (unchanged on exit)                      |
23  C     |   phiHyd(i,j,1:k-1) is the hydrostatic Potential         |  C     |   phiHyd(i,j,1:k-1) is the hydrostatic Potential         |
24  C     |                 at cell centers (tracer points)          |  C     |                 at cell centers (tracer points)          |
# Line 31  C     |  (ocean only-^) at cell the inte Line 36  C     |  (ocean only-^) at cell the inte
36  C     | Atmosphere:                                              |  C     | Atmosphere:                                              |
37  C     |   Integr_GeoPot allows to select one integration method  |  C     |   Integr_GeoPot allows to select one integration method  |
38  C     |    (see the list below)                                  |  C     |    (see the list below)                                  |
39  C     \==========================================================/  C     *==========================================================*
40    C     \ev
41    C     !USES:
42        IMPLICIT NONE        IMPLICIT NONE
43  C     == Global variables ==  C     == Global variables ==
44  #include "SIZE.h"  #include "SIZE.h"
45  #include "GRID.h"  #include "GRID.h"
46  #include "EEPARAMS.h"  #include "EEPARAMS.h"
47  #include "PARAMS.h"  #include "PARAMS.h"
48    #include "FFIELDS.h"
49  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
50  #include "tamc.h"  #include "tamc.h"
51  #include "tamc_keys.h"  #include "tamc_keys.h"
52  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
53    #include "SURFACE.h"
54    #include "DYNVARS.h"
55    
56    C     !INPUT/OUTPUT PARAMETERS:
57  C     == Routine arguments ==  C     == Routine arguments ==
58        INTEGER bi,bj,iMin,iMax,jMin,jMax,K        INTEGER bi,bj,iMin,iMax,jMin,jMax,K
59        _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL tFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
60        _RL salt(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _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)        _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
62        INTEGER myThid        INTEGER myThid
63                
64  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
65    
66    C     !LOCAL VARIABLES:
67  C     == Local variables ==  C     == Local variables ==
68        INTEGER i,j, Kp1        INTEGER i,j, Kp1
69        _RL zero, one, half        _RL zero, one, half
70        _RL alphaRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL alphaRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71        _RL dRloc,dRlocKp1        _RL dRloc,dRlocKp1,locAlpha
72        _RL ddPI, ddPIm, ddPIp, ratioRp, ratioRm        _RL ddPI, ddPIm, ddPIp, ratioRp, ratioRm
73    CEOP
74    
75        zero = 0. _d 0        zero = 0. _d 0
76        one  = 1. _d 0        one  = 1. _d 0
# Line 108  C       P(z=eta) = P(atmospheric_loading Line 121  C       P(z=eta) = P(atmospheric_loading
121          IF (k.EQ.1) THEN          IF (k.EQ.1) THEN
122            DO j=jMin,jMax            DO j=jMin,jMax
123              DO i=iMin,iMax              DO i=iMin,iMax
124  C             *NOTE* The loading should go here but has not been implemented yet  #ifdef ATMOSPHERIC_LOADING
125                phiHyd(i,j,k)=0.                phiHyd(i,j,k)=pload(i,j,bi,bj)*recip_rhoConst
126    #else
127                  phiHyd(i,j,k)=0. _d 0
128    #endif
129              ENDDO              ENDDO
130            ENDDO            ENDDO
131          ENDIF          ENDIF
# Line 117  C             *NOTE* The loading should Line 133  C             *NOTE* The loading should
133  C       Calculate density  C       Calculate density
134  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
135              kkey = (ikey-1)*Nr + k              kkey = (ikey-1)*Nr + k
136  CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE tFld(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
137  CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
138  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
139          CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,          CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k,
140       &                 theta, salt,       &                 tFld, sFld,
141       &                 alphaRho, myThid)       &                 alphaRho, myThid)
142    
143  C       Hydrostatic pressure at cell centers  C       Hydrostatic pressure at cell centers
# Line 135  c           within the k-loop. Line 151  c           within the k-loop.
151  CADJ GENERAL  CADJ GENERAL
152  #endif      /* ALLOW_AUTODIFF_TAMC */  #endif      /* ALLOW_AUTODIFF_TAMC */
153    
154  C---------- This discretization is the "finite volume" form  CmlC---------- This discretization is the "finite volume" form
155  C           which has not been used to date since it does not  CmlC           which has not been used to date since it does not
156  C           conserve KE+PE exactly even though it is more natural  CmlC           conserve KE+PE exactly even though it is more natural
157  C  CmlC
158  c           IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+  Cml          IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
159  c    &              drF(K)*gravity*alphaRho(i,j)*recip_rhoConst  Cml           phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
160  c           phiHyd(i,j,k)=phiHyd(i,j,k)+  Cml     &          + hFacC(i,j,k,bi,bj)
161  c    &          0.5*drF(K)*gravity*alphaRho(i,j)*recip_rhoConst  Cml     &            *drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
162  C-----------------------------------------------------------------------  Cml     &          + gravity*etaN(i,j,bi,bj)
163    Cml          ENDIF
164    Cml           IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
165    Cml     &         drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
166    Cml           phiHyd(i,j,k)=phiHyd(i,j,k)+
167    Cml     &          0.5*drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
168    CmlC-----------------------------------------------------------------------
169    
170  C---------- This discretization is the "energy conserving" form  C---------- This discretization is the "energy conserving" form
171  C           which has been used since at least Adcroft et al., MWR 1997  C           which has been used since at least Adcroft et al., MWR 1997
172  C  C
173                
174              phiHyd(i,j,k)=phiHyd(i,j,k)+              phiHyd(i,j,k)=phiHyd(i,j,k)+
175       &          0.5*dRloc*gravity*alphaRho(i,j)*recip_rhoConst       &          0.5*dRloc*gravity*alphaRho(i,j)*recip_rhoConst
176              IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+              IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
177       &          0.5*dRlocKp1*gravity*alphaRho(i,j)*recip_rhoConst       &          0.5*dRlocKp1*gravity*alphaRho(i,j)*recip_rhoConst
178  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
179    
180    C---------- Compute bottom pressure deviation from gravity*rho0*H
181    C           This has to be done starting from phiHyd at the current
182    C           tracer point and .5 of the cell's thickness has to be
183    C           substracted from hFacC
184                IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
185                 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
186         &              + (hFacC(i,j,k,bi,bj)-.5)*drF(K)
187         &                   *gravity*alphaRho(i,j)*recip_rhoConst
188         &              + gravity*etaN(i,j,bi,bj)
189                ENDIF
190    C-----------------------------------------------------------------------
191    
192            ENDDO            ENDDO
193          ENDDO          ENDDO
194                    
195          ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
196    C       This is the hydrostatic pressure calculation for the Ocean
197    C       which uses the FIND_RHO() routine to calculate density
198    C       before integrating g*rho over the current layer/interface
199    #ifdef      ALLOW_AUTODIFF_TAMC
200    CADJ GENERAL
201    #endif      /* ALLOW_AUTODIFF_TAMC */
202    
203            dRloc=drC(k)
204            IF (k.EQ.1) dRloc=drF(1)
205            IF (k.EQ.Nr) THEN
206              dRlocKp1=0.
207            ELSE
208              dRlocKp1=drC(k+1)
209            ENDIF
210    
211            IF (k.EQ.1) THEN
212              DO j=jMin,jMax
213                DO i=iMin,iMax
214                  phiHyd(i,j,k)=0.
215                  phiHyd(i,j,k)=pload(i,j,bi,bj)
216                ENDDO
217              ENDDO
218            ENDIF
219    
220    C       Calculate density
221    #ifdef ALLOW_AUTODIFF_TAMC
222                kkey = (ikey-1)*Nr + k
223    CADJ STORE tFld(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
224    CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
225    #endif /* ALLOW_AUTODIFF_TAMC */
226            CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k,
227         &                 tFld, sFld,
228         &                 alphaRho, myThid)
229    
230    C       Hydrostatic pressure at cell centers
231            DO j=jMin,jMax
232              DO i=iMin,iMax
233                locAlpha=alphaRho(i,j)+rhoConst
234                IF (locAlpha.NE.0.) locAlpha=maskC(i,j,k,bi,bj)/locAlpha
235    
236    CmlC---------- This discretization is the "finite volume" form
237    CmlC           which has not been used to date since it does not
238    CmlC           conserve KE+PE exactly even though it is more natural
239    CmlC
240    Cml            IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
241    Cml             phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
242    Cml     &          + hFacC(i,j,k,bi,bj)*drF(K)*locAlpha
243    Cml     &          + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
244    Cml            ENDIF
245    Cml            IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
246    Cml     &           drF(K)*locAlpha
247    Cml            phiHyd(i,j,k)=phiHyd(i,j,k)+
248    Cml     &           0.5*drF(K)*locAlpha
249    CmlC-----------------------------------------------------------------------
250    
251    C---------- This discretization is the "energy conserving" form
252    C           which has been used since at least Adcroft et al., MWR 1997
253    C
254    
255                phiHyd(i,j,k)=phiHyd(i,j,k)+
256         &          0.5*dRloc*locAlpha
257                IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
258         &          0.5*dRlocKp1*locAlpha
259    
260    C-----------------------------------------------------------------------
261    
262    C---------- Compute gravity*(sea surface elevation) first
263    C           This has to be done starting from phiHyd at the current
264    C           tracer point and .5 of the cell's thickness has to be
265    C           substracted from hFacC
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)-0.5)*drF(k)*locAlpha
269         &              + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
270                ENDIF
271    C-----------------------------------------------------------------------
272    
273              ENDDO
274            ENDDO
275    
276        ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN        ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
277  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 170  C       Integrate d Phi / d pi Line 285  C       Integrate d Phi / d pi
285  C  --  Energy Conserving Form, No hFac  --  C  --  Energy Conserving Form, No hFac  --
286  C------------ The integration for the first level phi(k=1) is the same  C------------ The integration for the first level phi(k=1) is the same
287  C             for both the "finite volume" and energy conserving methods.  C             for both the "finite volume" and energy conserving methods.
288  C    *NOTE* o Working with geopotential Anomaly, the geopotential boundary  Ci    *NOTE* o Working with geopotential Anomaly, the geopotential boundary
289  C             condition is simply Phi'(Ro_surf)=0.  C             condition is simply Phi-prime(Ro_surf)=0.
290  C           o convention ddPI > 0 (same as drF & drC)  C           o convention ddPI > 0 (same as drF & drC)
291  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
292          IF (K.EQ.1) THEN          IF (K.EQ.1) THEN
# Line 181  C--------------------------------------- Line 296  C---------------------------------------
296             DO i=iMin,iMax             DO i=iMin,iMax
297               phiHyd(i,j,K)=               phiHyd(i,j,K)=
298       &          ddPIp*maskC(i,j,K,bi,bj)       &          ddPIp*maskC(i,j,K,bi,bj)
299       &               *(theta(I,J,K,bi,bj)-tRef(K))       &               *(tFld(I,J,K,bi,bj)-tRef(K))
300             ENDDO             ENDDO
301            ENDDO            ENDDO
302          ELSE          ELSE
# Line 192  C-------- This discretization is the ene Line 307  C-------- This discretization is the ene
307             DO i=iMin,iMax             DO i=iMin,iMax
308                phiHyd(i,j,K)=phiHyd(i,j,K-1)                phiHyd(i,j,K)=phiHyd(i,j,K-1)
309       &           +ddPI*maskC(i,j,K-1,bi,bj)       &           +ddPI*maskC(i,j,K-1,bi,bj)
310       &                *(theta(I,J,K-1,bi,bj)-tRef(K-1))       &                *(tFld(I,J,K-1,bi,bj)-tRef(K-1))
311       &           +ddPI*maskC(i,j, K ,bi,bj)       &           +ddPI*maskC(i,j, K ,bi,bj)
312       &                *(theta(I,J, K ,bi,bj)-tRef( K ))       &                *(tFld(I,J, K ,bi,bj)-tRef( K ))
313  C             Old code (atmos-exact) looked like this  C             Old code (atmos-exact) looked like this
314  Cold          phiHyd(i,j,K)=phiHyd(i,j,K-1) - ddPI*  Cold          phiHyd(i,j,K)=phiHyd(i,j,K-1) - ddPI*
315  Cold &      (theta(I,J,K-1,bi,bj)+theta(I,J,K,bi,bj)-2.*tRef(K))  Cold &      (tFld(I,J,K-1,bi,bj)+tFld(I,J,K,bi,bj)-2.*tRef(K))
316             ENDDO             ENDDO
317            ENDDO            ENDDO
318          ENDIF          ENDIF
# Line 220  C--------- Line 335  C---------
335            DO j=jMin,jMax            DO j=jMin,jMax
336             DO i=iMin,iMax             DO i=iMin,iMax
337               phiHyd(i,j,K) =               phiHyd(i,j,K) =
338       &          ddPIp*hFacC(I,J, K ,bi,bj)       &          ddPIp*_hFacC(I,J, K ,bi,bj)
339       &               *(theta(I,J, K ,bi,bj)-tRef( K ))       &               *(tFld(I,J, K ,bi,bj)-tRef( K ))
340             ENDDO             ENDDO
341            ENDDO            ENDDO
342          ELSE          ELSE
# Line 232  C--------- Line 347  C---------
347            DO j=jMin,jMax            DO j=jMin,jMax
348             DO i=iMin,iMax             DO i=iMin,iMax
349               phiHyd(i,j,K) = phiHyd(i,j,K-1)               phiHyd(i,j,K) = phiHyd(i,j,K-1)
350       &         +ddPIm*hFacC(I,J,K-1,bi,bj)       &         +ddPIm*_hFacC(I,J,K-1,bi,bj)
351       &               *(theta(I,J,K-1,bi,bj)-tRef(K-1))       &               *(tFld(I,J,K-1,bi,bj)-tRef(K-1))
352       &         +ddPIp*hFacC(I,J, K ,bi,bj)       &         +ddPIp*_hFacC(I,J, K ,bi,bj)
353       &               *(theta(I,J, K ,bi,bj)-tRef( K ))       &               *(tFld(I,J, K ,bi,bj)-tRef( K ))
354             ENDDO             ENDDO
355            ENDDO            ENDDO
356          ENDIF          ENDIF
# Line 258  C--------- Line 373  C---------
373            DO j=jMin,jMax            DO j=jMin,jMax
374             DO i=iMin,iMax             DO i=iMin,iMax
375               phiHyd(i,j,K) =               phiHyd(i,j,K) =
376       &        ( ddPIm*max(zero, hFacC(i,j,K,bi,bj)-half)       &        ( ddPIm*max(zero, _hFacC(i,j,K,bi,bj)-half)
377       &         +ddPIp*min(zero, hFacC(i,j,K,bi,bj)-half) )       &         +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)-half) )
378       &               *(theta(i,j, K ,bi,bj)-tRef( K ))       &               *(tFld(i,j, K ,bi,bj)-tRef( K ))
379       &               * maskC(i,j, K ,bi,bj)       &               * maskC(i,j, K ,bi,bj)
380             ENDDO             ENDDO
381            ENDDO            ENDDO
# Line 273  C--------- Line 388  C---------
388             DO i=iMin,iMax             DO i=iMin,iMax
389               phiHyd(i,j,K) = phiHyd(i,j,K-1)               phiHyd(i,j,K) = phiHyd(i,j,K-1)
390       &        + ddPIm*0.5       &        + ddPIm*0.5
391       &               *(theta(i,j,K-1,bi,bj)-tRef(K-1))       &               *(tFld(i,j,K-1,bi,bj)-tRef(K-1))
392       &               * maskC(i,j,K-1,bi,bj)       &               * maskC(i,j,K-1,bi,bj)
393       &        +(ddPIm*max(zero, hFacC(i,j,K,bi,bj)-half)       &        +(ddPIm*max(zero, _hFacC(i,j,K,bi,bj)-half)
394       &         +ddPIp*min(zero, hFacC(i,j,K,bi,bj)-half) )       &         +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)-half) )
395       &               *(theta(i,j, K ,bi,bj)-tRef( K ))       &               *(tFld(i,j, K ,bi,bj)-tRef( K ))
396       &               * maskC(i,j, K ,bi,bj)       &               * maskC(i,j, K ,bi,bj)
397             ENDDO             ENDDO
398            ENDDO            ENDDO
# Line 303  C--------- Line 418  C---------
418            DO j=jMin,jMax            DO j=jMin,jMax
419             DO i=iMin,iMax             DO i=iMin,iMax
420               phiHyd(i,j,K) =               phiHyd(i,j,K) =
421       &        ( ddPIm*max(zero,(hFacC(i,j,K,bi,bj)-one)*ratioRm+half)       &        ( ddPIm*max(zero,(_hFacC(i,j,K,bi,bj)-one)*ratioRm+half)
422       &         +ddPIp*min(zero, hFacC(i,j,K,bi,bj)*ratioRp     -half) )       &         +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)*ratioRp     -half) )
423       &               *(theta(i,j, K ,bi,bj)-tRef( K ))       &               *(tFld(i,j, K ,bi,bj)-tRef( K ))
424       &               * maskC(i,j, K ,bi,bj)       &               * maskC(i,j, K ,bi,bj)
425             ENDDO             ENDDO
426            ENDDO            ENDDO
# Line 320  C--------- Line 435  C---------
435             DO i=iMin,iMax             DO i=iMin,iMax
436               phiHyd(i,j,K) = phiHyd(i,j,K-1)               phiHyd(i,j,K) = phiHyd(i,j,K-1)
437       &        + ddPIm*0.5       &        + ddPIm*0.5
438       &               *(theta(i,j,K-1,bi,bj)-tRef(K-1))       &               *(tFld(i,j,K-1,bi,bj)-tRef(K-1))
439       &               * maskC(i,j,K-1,bi,bj)       &               * maskC(i,j,K-1,bi,bj)
440       &        +(ddPIm*max(zero,(hFacC(i,j,K,bi,bj)-one)*ratioRm+half)       &        +(ddPIm*max(zero,(_hFacC(i,j,K,bi,bj)-one)*ratioRm+half)
441       &         +ddPIp*min(zero, hFacC(i,j,K,bi,bj)*ratioRp     -half) )       &         +ddPIp*min(zero, _hFacC(i,j,K,bi,bj)*ratioRp     -half) )
442       &               *(theta(i,j, K ,bi,bj)-tRef( K ))       &               *(tFld(i,j, K ,bi,bj)-tRef( K ))
443       &               * maskC(i,j, K ,bi,bj)       &               * maskC(i,j, K ,bi,bj)
444             ENDDO             ENDDO
445            ENDDO            ENDDO

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.21

  ViewVC Help
Powered by ViewVC 1.1.22