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

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

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

revision 1.22 by heimbach, Mon Sep 11 22:59:08 2000 UTC revision 1.50 by heimbach, Fri Feb 13 21:56:48 2009 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7  CStartOfInterFace  CBOP
8        SUBROUTINE CALC_GS(  C     !ROUTINE: CALC_GS
9    C     !INTERFACE:
10          SUBROUTINE CALC_GS(
11       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
12       I           xA,yA,uTrans,vTrans,rTrans,maskup,maskC,       I           xA, yA, maskUp, uFld, vFld, wFld,
13         I           uTrans, vTrans, rTrans, rTransKp1,
14       I           KappaRS,       I           KappaRS,
15       U           af,df,fZon,fMer,fVerS,       U           fVerS,
16       I           myCurrentTime, myThid )       I           myTime,myIter,myThid )
17  C     /==========================================================\  C     !DESCRIPTION: \bv
18  C     | SUBROUTINE CALC_GS                                       |  C     *==========================================================*
19  C     | o Calculate the salt tendency terms.                     |  C     | SUBROUTINE CALC_GS
20  C     |==========================================================|  C     | o Calculate the salt tendency terms.
21  C     | A procedure called EXTERNAL_FORCING_S is called from     |  C     *==========================================================*
22  C     | here. These procedures can be used to add per problem    |  C     | A procedure called EXTERNAL_FORCING_S is called from
23  C     | E-P  flux source terms.                                  |  C     | here. These procedures can be used to add per problem
24  C     | Note: Although it is slightly counter-intuitive the      |  C     | E-P  flux source terms.
25  C     |       EXTERNAL_FORCING routine is not the place to put   |  C     | Note: Although it is slightly counter-intuitive the
26  C     |       file I/O. Instead files that are required to       |  C     |       EXTERNAL_FORCING routine is not the place to put
27  C     |       calculate the external source terms are generally  |  C     |       file I/O. Instead files that are required to
28  C     |       read during the model main loop. This makes the    |  C     |       calculate the external source terms are generally
29  C     |       logisitics of multi-processing simpler and also    |  C     |       read during the model main loop. This makes the
30  C     |       makes the adjoint generation simpler. It also      |  C     |       logisitics of multi-processing simpler and also
31  C     |       allows for I/O to overlap computation where that   |  C     |       makes the adjoint generation simpler. It also
32  C     |       is supported by hardware.                          |  C     |       allows for I/O to overlap computation where that
33  C     | Aside from the problem specific term the code here       |  C     |       is supported by hardware.
34  C     | forms the tendency terms due to advection and mixing     |  C     | Aside from the problem specific term the code here
35  C     | The baseline implementation here uses a centered         |  C     | forms the tendency terms due to advection and mixing
36  C     | difference form for the advection term and a tensorial   |  C     | The baseline implementation here uses a centered
37  C     | divergence of a flux form for the diffusive term. The    |  C     | difference form for the advection term and a tensorial
38  C     | diffusive term is formulated so that isopycnal mixing and|  C     | divergence of a flux form for the diffusive term. The
39  C     | GM-style subgrid-scale terms can be incorporated b simply|  C     | diffusive term is formulated so that isopycnal mixing and
40  C     | setting the diffusion tensor terms appropriately.        |  C     | GM-style subgrid-scale terms can be incorporated b simply
41  C     \==========================================================/  C     | setting the diffusion tensor terms appropriately.
42        IMPLICIT NONE  C     *==========================================================*
43    C     \ev
44    
45    C     !USES:
46          IMPLICIT NONE
47  C     == GLobal variables ==  C     == GLobal variables ==
48  #include "SIZE.h"  #include "SIZE.h"
49  #include "DYNVARS.h"  #include "DYNVARS.h"
50  #include "EEPARAMS.h"  #include "EEPARAMS.h"
51  #include "PARAMS.h"  #include "PARAMS.h"
52  #include "GRID.h"  #include "RESTART.h"
53  #include "FFIELDS.h"  #ifdef ALLOW_GENERIC_ADVDIFF
54    #include "GAD.h"
55    #endif
56    #ifdef ALLOW_AUTODIFF_TAMC
57    # include "tamc.h"
58    # include "tamc_keys.h"
59    #endif
60    
61    C     !INPUT/OUTPUT PARAMETERS:
62  C     == Routine arguments ==  C     == Routine arguments ==
63  C     fZon    - Work array for flux of temperature in the east-west  C     bi, bj,   :: tile indices
64  C               direction at the west face of a cell.  C     iMin,iMax, jMin,jMax :: Range of points for which calculation
65  C     fMer    - Work array for flux of temperature in the north-south  C                                       results will be set.
66  C               direction at the south face of a cell.  C     k         :: vertical index
67  C     fVerS   - Flux of salt (S) in the vertical  C     kM1       :: =k-1 for k>1, =1 for k=1
68  C               direction at the upper(U) and lower(D) faces of a cell.  C     kUp       :: index into 2 1/2D array, toggles between 1|2
69  C     maskUp  - Land mask used to denote base of the domain.  C     kDown     :: index into 2 1/2D array, toggles between 2|1
70  C     maskC   - Land mask for salt cells (used in TOP_LAYER only)  C     xA        :: Tracer cell face area normal to X
71  C     xA      - Tracer cell face area normal to X  C     yA        :: Tracer cell face area normal to X
72  C     yA      - Tracer cell face area normal to X  C     maskUp    :: Land mask used to denote base of the domain.
73  C     uTrans  - Zonal volume transport through cell face  C     uFld,vFld :: Local copy of horizontal velocity field
74  C     vTrans  - Meridional volume transport through cell face  C     wFld      :: Local copy of vertical velocity field
75  C     rTrans  - Vertical volume transport through cell face  C     uTrans    :: Zonal volume transport through cell face
76  C     af      - Advective flux component work array  C     vTrans    :: Meridional volume transport through cell face
77  C     df      - Diffusive flux component work array  C     rTrans    ::   Vertical volume transport at interface k
78  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  C     rTransKp1 :: Vertical volume transport at inteface k+1
79  C                                      results will be set.  C     KappaRS   :: Vertical diffusion for Salinity
80  C     myThid - Instance number for this innvocation of CALC_GT  C     fVerS     :: Flux of salt (S) in the vertical direction
81        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  C                  at the upper(U) and lower(D) faces of a cell.
82        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  C     myTime    :: current time
83        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)  C     myIter    :: current iteration number
84        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  C     myThid    :: my Thread Id. number
85        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       INTEGER k,kUp,kDown,kM1  
86        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
87        _RL     myCurrentTime        INTEGER k,kUp,kDown,kM1
88          _RS xA     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89          _RS yA     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90          _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91          _RL uFld   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92          _RL vFld   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93          _RL wFld   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94          _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95          _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96          _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98          _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99          _RL fVerS  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
100          _RL     myTime
101          INTEGER myIter
102        INTEGER myThid        INTEGER myThid
103  CEndOfInterface  CEOP
104    
105  C     == Local variables ==  #ifdef ALLOW_GENERIC_ADVDIFF
106  C     I, J, K - Loop counters  C     === Local variables ===
107        INTEGER i,j        LOGICAL calcAdvection
108        LOGICAL TOP_LAYER        INTEGER iterNb
109        _RL afFacS, dfFacS  #ifdef ALLOW_ADAMSBASHFORTH_3
110        _RL dSdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        INTEGER m1, m2
111        _RL dSdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  #endif
112        _RL df4   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
113    #ifdef ALLOW_AUTODIFF_TAMC
114              act1 = bi - myBxLo(myThid)
115              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
116              act2 = bj - myByLo(myThid)
117              max2 = myByHi(myThid) - myByLo(myThid) + 1
118              act3 = myThid - 1
119              max3 = nTx*nTy
120              act4 = ikey_dynamics - 1
121              itdkey = (act1 + 1) + act2*max1
122         &                      + act3*max1*max2
123         &                      + act4*max1*max2*max3
124              kkey = (itdkey-1)*Nr + k
125    #endif /* ALLOW_AUTODIFF_TAMC */
126    
127  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
128  C--   only the kUp part of fverS is set in this subroutine  C--   only the kUp part of fverS is set in this subroutine
129  C--   the kDown is still required  C--   the kDown is still required
   
130        fVerS(1,1,kDown) = fVerS(1,1,kDown)        fVerS(1,1,kDown) = fVerS(1,1,kDown)
131        DO j=1-OLy,sNy+OLy  # ifdef NONLIN_FRSURF
132         DO i=1-OLx,sNx+OLx  CADJ STORE fVerS(:,:,:) =
133          fZon(i,j)      = 0.0  CADJ &     comlev1_bibj_k, key=kkey, byte=isbyte,
134          fMer(i,j)      = 0.0  CADJ &     kind = isbyte
135          fVerS(i,j,kUp) = 0.0  CADJ STORE gsNm1(:,:,k,bi,bj) =
136         ENDDO  CADJ &     comlev1_bibj_k, key=kkey, byte=isbyte,
137        ENDDO  CADJ &     kind = isbyte
138  #endif  # endif
139    #endif
140        afFacS = 1. _d 0  
141        dfFacS = 1. _d 0  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142        TOP_LAYER = K .EQ. 1  
143          calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec
144  C---  Calculate advective and diffusive fluxes between cells.        iterNb = myIter
145          IF (staggerTimeStep) iterNb = myIter - 1
146  #ifdef INCLUDE_T_DIFFUSION_CODE  
147  C     o Zonal tracer gradient  #ifdef ALLOW_ADAMSBASHFORTH_3
148        DO j=1-Oly,sNy+Oly          m1 = 1 + MOD(iterNb+1,2)
149         DO i=1-Olx+1,sNx+Olx          m2 = 1 + MOD( iterNb ,2)
150          dSdx(i,j) = _recip_dxC(i,j,bi,bj)*          CALL GAD_CALC_RHS(
151       &  (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
152         ENDDO       I           xA, yA, maskUp, uFld, vFld, wFld,
153        ENDDO       I           uTrans, vTrans, rTrans, rTransKp1,
154  C     o Meridional tracer gradient       I           diffKhS, diffK4S, KappaRS,
155        DO j=1-Oly+1,sNy+Oly       I           gsNm(1-Olx,1-Oly,1,1,1,m2), salt,
156         DO i=1-Olx,sNx+Olx       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
157          dSdy(i,j) = _recip_dyC(i,j,bi,bj)*       I           calcAdvection, saltImplVertAdv, AdamsBashforth_S,
158       &  (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))       I           useGMRedi, useKPP,
159         ENDDO       U           fVerS, gS,
160        ENDDO       I           myTime, myIter, myThid )
161    #else /* ALLOW_ADAMSBASHFORTH_3 */
162  C--   del^2 of S, needed for bi-harmonic (del^4) term          CALL GAD_CALC_RHS(
163        IF (diffK4S .NE. 0.) THEN       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
164         DO j=1-Oly+1,sNy+Oly-1       I           xA, yA, maskUp, uFld, vFld, wFld,
165          DO i=1-Olx+1,sNx+Olx-1       I           uTrans, vTrans, rTrans, rTransKp1,
166           df4(i,j)= _recip_hFacC(i,j,k,bi,bj)       I           diffKhS, diffK4S, KappaRS, gsNm1, salt,
167       &             *recip_drF(k)/_rA(i,j,bi,bj)       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
168       &            *(       I           calcAdvection, saltImplVertAdv, AdamsBashforth_S,
169       &             +( xA(i+1,j)*dSdx(i+1,j)-xA(i,j)*dSdx(i,j) )       I           useGMRedi, useKPP,
170       &             +( yA(i,j+1)*dSdy(i,j+1)-yA(i,j)*dSdy(i,j) )       U           fVerS, gS,
171       &             )       I           myTime, myIter, myThid )
172          ENDDO  #endif /* ALLOW_ADAMSBASHFORTH_3 */
173         ENDDO  
174        ENDIF  C--   External salinity forcing term(s) inside Adams-Bashforth:
175  #endif        IF ( saltForcing .AND. tracForcingOutAB.NE.1 )
176         & CALL EXTERNAL_FORCING_S(
177         I     iMin,iMax,jMin,jMax,bi,bj,k,
178         I     myTime,myThid)
179    
180  C--   Zonal flux (fZon is at west face of "salt" cell)        IF ( AdamsBashforthGs ) THEN
181  C     Advective component of zonal flux  #ifdef ALLOW_ADAMSBASHFORTH_3
182        DO j=jMin,jMax          CALL ADAMS_BASHFORTH3(
183         DO i=iMin,iMax       I                        bi, bj, k,
184          af(i,j) =       U                        gS, gsNm,
185       &   uTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i-1,j,k,bi,bj))*0.5 _d 0       I                        saltStartAB, iterNb, myThid )
186         ENDDO  #else
187        ENDDO          CALL ADAMS_BASHFORTH2(
188  C     o Diffusive component of zonal flux       I                        bi, bj, k,
189        DO j=jMin,jMax       U                        gS, gsNm1,
190         DO i=iMin,iMax       I                        saltStartAB, iterNb, myThid )
         df(i,j) = -diffKhS*xA(i,j)*dSdx(i,j)  
        ENDDO  
       ENDDO  
 #ifdef ALLOW_GMREDI  
       IF (useGMRedi) CALL GMREDI_XTRANSPORT(  
      I     iMin,iMax,jMin,jMax,bi,bj,K,  
      I     xA,salt,  
      U     df,  
      I     myThid)  
191  #endif  #endif
 C     o Add the bi-harmonic contribution  
       IF (diffK4S .NE. 0.) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = df(i,j) + xA(i,j)*  
      &    diffK4S*(df4(i,j)-df4(i-1,j))*_recip_dxC(i,j,bi,bj)  
         ENDDO  
        ENDDO  
       ENDIF  
 C     Net zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fZon(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Meridional flux (fMer is at south face of "salt" cell)  
 C     Advective component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
 C       Advective component of meridional flux  
         af(i,j) =  
      &   vTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j-1,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Diffusive component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = -diffKhS*yA(i,j)*dSdy(i,j)  
        ENDDO  
       ENDDO  
 #ifdef ALLOW_GMREDI  
       IF (useGMRedi) CALL GMREDI_YTRANSPORT(  
      I     iMin,iMax,jMin,jMax,bi,bj,K,  
      I     yA,salt,  
      U     df,  
      I     myThid)  
 #endif  
 C     o Add the bi-harmonic contribution  
       IF (diffK4S .NE. 0.) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = df(i,j) + yA(i,j)*  
      &    diffK4S*(df4(i,j)-df4(i,j-1))*_recip_dyC(i,j,bi,bj)  
         ENDDO  
        ENDDO  
       ENDIF  
   
 C     Net meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fMer(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Vertical flux (fVerS) above  
 C     Advective component of vertical flux  
 C     Note: For K=1 then KM1=1 this gives a barZ(T) = T  
 C     (this plays the role of the free-surface correction)  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   rTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j,kM1,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     o Diffusive component of vertical flux  
 C     Note: For K=1 then KM1=1 and this gives a dS/dr = 0 upper  
 C           boundary condition.  
       IF (implicitDiffusion) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = 0.  
         ENDDO  
        ENDDO  
       ELSE  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = - _rA(i,j,bi,bj)*(  
      &    KappaRS(i,j,k)*recip_drC(k)  
      &    *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))*rkFac  
      &    )  
         ENDDO  
        ENDDO  
192        ENDIF        ENDIF
193    
194  #ifdef ALLOW_GMREDI  C--   External salinity forcing term(s) outside Adams-Bashforth:
195        IF (useGMRedi) CALL GMREDI_RTRANSPORT(        IF ( saltForcing .AND. tracForcingOutAB.EQ.1 )
196       I     iMin,iMax,jMin,jMax,bi,bj,K,       & CALL EXTERNAL_FORCING_S(
197       I     maskUp,salt,       I     iMin,iMax,jMin,jMax,bi,bj,k,
198       U     df,       I     myTime,myThid)
      I     myThid)  
 #endif  
199    
200  #ifdef ALLOW_KPP  #ifdef NONLIN_FRSURF
201  C--   Add non-local KPP transport term (ghat) to diffusive salt flux.        IF (nonlinFreeSurf.GT.0) THEN
202        IF (useKPP) CALL KPP_TRANSPORT_S(          CALL FREESURF_RESCALE_G(
203       I     iMin,iMax,jMin,jMax,bi,bj,k,km1,       I                          bi, bj, k,
204       I     maskC,KappaRS,       U                          gS,
205       U     df )       I                          myThid )
206            IF ( AdamsBashforthGs ) THEN
207    #ifdef ALLOW_ADAMSBASHFORTH_3
208            CALL FREESURF_RESCALE_G(
209         I                          bi, bj, k,
210         U                          gsNm(1-OLx,1-OLy,1,1,1,1),
211         I                          myThid )
212            CALL FREESURF_RESCALE_G(
213         I                          bi, bj, k,
214         U                          gsNm(1-OLx,1-OLy,1,1,1,2),
215         I                          myThid )
216    #else
217            CALL FREESURF_RESCALE_G(
218         I                          bi, bj, k,
219         U                          gsNm1,
220         I                          myThid )
221  #endif  #endif
222            ENDIF
 C     Net vertical flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fVerS(i,j,kUp) = ( afFacS*af(i,j)+  dfFacS*df(i,j) )*maskUp(i,j)  
        ENDDO  
       ENDDO  
       IF ( TOP_LAYER ) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          fVerS(i,j,kUp) = afFacS*af(i,j)*freeSurfFac  
         ENDDO  
        ENDDO  
223        ENDIF        ENDIF
224    #endif /* NONLIN_FRSURF */
225    
226  C--   Tendency is minus divergence of the fluxes.  #endif /* ALLOW_GENERIC_ADVDIFF */
 C     Note. Tendency terms will only be correct for range  
 C           i=iMin+1:iMax-1, j=jMin+1:jMax-1. Edge points  
 C           will contain valid floating point numbers but  
 C           they are not algorithmically correct. These points  
 C           are not used.  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
 #define _recip_VolS1(i,j,k,bi,bj) _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  
 #define _recip_VolS2(i,j,k,bi,bj) /_rA(i,j,bi,bj)  
         gS(i,j,k,bi,bj)=  
      &   -_recip_VolS1(i,j,k,bi,bj)  
      &    _recip_VolS2(i,j,k,bi,bj)  
      &   *(  
      &    +( fZon(i+1,j)-fZon(i,j) )  
      &    +( fMer(i,j+1)-fMer(i,j) )  
      &    +( fVerS(i,j,kUp)-fVerS(i,j,kDown) )*rkFac  
      &    )  
        ENDDO  
       ENDDO  
   
 C--   External forcing term(s)  
       CALL EXTERNAL_FORCING_S(  
      I     iMin,iMax,jMin,jMax,bi,bj,k,  
      I     maskC,  
      I     myCurrentTime,myThid)  
   
 #ifdef INCLUDE_LAT_CIRC_FFT_FILTER_CODE  
 C--  
       CALL FILTER_LATCIRCS_FFT_APPLY( gS, 1, sNy, k, k, bi, bj, 1, myThid)  
 #endif  
227    
228        RETURN        RETURN
229        END        END

Legend:
Removed from v.1.22  
changed lines
  Added in v.1.50

  ViewVC Help
Powered by ViewVC 1.1.22