/[MITgcm]/MITgcm/pkg/exf/exf_interp.F
ViewVC logotype

Diff of /MITgcm/pkg/exf/exf_interp.F

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

revision 1.16 by dimitri, Sat Jul 1 03:20:33 2006 UTC revision 1.23 by mlosch, Thu Jan 24 08:29:51 2008 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "EXF_OPTIONS.h"  #include "EXF_OPTIONS.h"
5    
6  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
7  C Flux Coupler using                       C  C Flux Coupler using                       C
8  C Bilinear interpolation of forcing fields C  C Bilinear interpolation of forcing fields C
# Line 9  C added Bicubic (bnc 1/2003) Line 13  C added Bicubic (bnc 1/2003)
13  C                                          C  C                                          C
14  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
15    
16          real*8 function lagran(i,x,a,sp)         _RL FUNCTION LAGRAN(i,x,a,sp)
17    
18          INTEGER i,k,sp          INTEGER i
19          _RS x          _RS x
20          real*8 a(4)          _RL a(4)
21          real*8 numer,denom          INTEGER sp
   
         numer = 1.D0  
         denom = 1.D0  
22    
23    C-      local variables:
24            INTEGER k
25            _RL numer,denom
26    
27            numer = 1. _d 0
28            denom = 1. _d 0
29    
30    #ifdef TARGET_NEC_SX
31    !CDIR UNROLL=8
32    #endif /* TARGET_NEC_SX */
33          do k=1,sp          do k=1,sp
34          if ( k .ne. i) then           if ( k .ne. i) then
35            denom = denom*(a(i) - a(k))            denom = denom*(a(i) - a(k))
36            numer = numer*(x    - a(k))            numer = numer*(x    - a(k))
37          endif           endif
38          enddo          enddo
39    
40          lagran = numer/denom          lagran = numer/denom
41    
42          return         RETURN
43          end         END
44    
45    
46         SUBROUTINE exf_interp(         SUBROUTINE exf_interp(
# Line 43  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC Line 54  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
54    
55        implicit none        implicit none
56    
57  C     infile       = name of the input file (direct access binary)  C  infile      (string)  :: name of the binary input file (direct access)
58  C     filePrec     = file precicision (currently not used, assumes real*4)  C  filePrec    (integer) :: number of bits per word in file (32 or 64)
59  C     arrout       = output arrays (different for each processor)  C  arrout      ( _RL )   :: output array
60  C     irecord      = record number in global file  C  irecord     (integer) :: record number to read
61  C     xG,yG        = coordinates for output grid  C     xG,yG              :: coordinates for output grid to interpolate to
62  C     lon_0, lat_0 = lon and lat of sw corner of global input grid  C     lon_0, lat_0       :: lon and lat of sw corner of global input grid
63  C     lon_inc      = scalar x-grid increment  C     lon_inc            :: scalar x-grid increment
64  C     lat_inc      = vector y-grid increments  C     lat_inc            :: vector y-grid increments
65  C     nx_in, ny_in = input x-grid and y-grid size  C  nx_in,ny_in (integer) :: size in x & y direction of input file to read
66  C     method       = 1,11,21 for bilinear; 2,12,22 for bicubic  C     method             :: 1,11,21 for bilinear; 2,12,22 for bicubic
67  C                    1,2 for tracer; 11,12 for U; 21,22 for V  C                        :: 1,2 for tracer; 11,12 for U; 21,22 for V
68  C     mythid       = thread id  C  myThid      (integer) :: My Thread Id number
69  C  C
70    
71  #include "SIZE.h"  #include "SIZE.h"
# Line 65  C subroutine variables Line 76  C subroutine variables
76        character*(*) infile        character*(*) infile
77        integer       filePrec, irecord, nx_in, ny_in        integer       filePrec, irecord, nx_in, ny_in
78        _RL           arrayout(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RL           arrayout(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
79        _RS           xG_in      (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RS           xG_in   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
80        _RS           yG      (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RS           yG      (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
81        _RL           lon_0, lon_inc        _RL           lon_0, lon_inc
82        _RL           lat_0, lat_inc(ny_in-1)        _RL           lat_0, lat_inc(ny_in-1)
83        integer       method, mythid        integer       method, mythid
84    
85    C functions
86          external lagran
87          _RL      lagran
88    
89  C local variables  C local variables
90        integer  e_ind(snx,sny),w_ind(snx,sny)        integer  e_ind(snx,sny),w_ind(snx,sny)
91        integer  n_ind(snx,sny),s_ind(snx,sny)        integer  n_ind(snx,sny),s_ind(snx,sny)
92        real*8   px_ind(4), py_ind(4), ew_val(4)        _RL      px_ind(4), py_ind(4), ew_val(4)
93        external lagran        _RL      arrayin(-1:nx_in+2 ,      -1:ny_in+2)
94        real*8   lagran        _RL      NorthValue
95        real*4   arrayin(-1:nx_in+2 ,      -1:ny_in+2)        _RL      x_in   (-1:nx_in+2), y_in(-1:ny_in+2)
       real*8   x_in   (-1:nx_in+2), y_in(-1:ny_in+2)  
       real*8   ninety      PARAMETER ( ninety = 90. )  
96        integer  i, j, k, l, js, bi, bj, sp, interp_unit        integer  i, j, k, l, js, bi, bj, sp, interp_unit
97    #ifdef TARGET_NEC_SX
98          integer  ic, ii, icnt
99          integer  inx(snx*sny,2)
100          _RL      ew_val1, ew_val2, ew_val3, ew_val4
101    #endif
102        _RS      xG(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RS      xG(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
103        _RS      threeSixtyRS, NorthValue        _RL      ninety
104          PARAMETER ( ninety = 90. )
105          _RS      threeSixtyRS
106        PARAMETER ( threeSixtyRS = 360. )        PARAMETER ( threeSixtyRS = 360. )
107    
108  C     put xG in interval [ lon_0 , lon_0+360 [  C     put xG in interval [ lon_0 , lon_0+360 [
# Line 102  C     put xG in interval [ lon_0 , lon_0 Line 122  C     put xG in interval [ lon_0 , lon_0
122       I   infile, filePrec,       I   infile, filePrec,
123       O   arrayin,       O   arrayin,
124       I   irecord, nx_in, ny_in, mythid)       I   irecord, nx_in, ny_in, mythid)
       _BARRIER  
125    
126  C     _BEGIN_MASTER( myThid )  C setup input longitude grid
127          do i=-1,nx_in+2
128  C setup input grid         x_in(i) = lon_0 + (i-1)*lon_inc
129         do i=-1,nx_in+2        enddo
         x_in(i) = lon_0 + (i-1)*lon_inc  
        enddo  
130    
131         y_in(0) = lat_0 - lat_inc(1)  C setup input latitude grid
132         y_in(-1)= lat_0 - 2.*lat_inc(1)        y_in(0) = lat_0 - lat_inc(1)
133         y_in(1) = lat_0        y_in(-1)= lat_0 - 2.*lat_inc(1)
134         do j=2,ny_in        y_in(1) = lat_0
135          y_in(j) = y_in(j-1) + lat_inc(j-1)        do j=2,ny_in
136         enddo         y_in(j) = y_in(j-1) + lat_inc(j-1)
137  c       y_in(ny_in+1) = y_in(ny_in) + lat_inc(ny_in-1)        enddo
138  c       y_in(ny_in+2) = y_in(ny_in) + 2.*lat_inc(ny_in-1)        do j=ny_in+1,ny_in+2
139         y_in(ny_in+1) = min( y_in(ny_in) + lat_inc(ny_in-1), ninety )         if (y_in(j-1).eq.ninety) then
140         y_in(ny_in+2) = min( y_in(ny_in) + 2.*lat_inc(ny_in-1), ninety )          y_in(j) = 2 * ninety - y_in(j-2)
141           else
142            y_in(j) = min( y_in(j-1)+lat_inc(ny_in-1), ninety )
143           endif
144          enddo
145    
146  C enlarge boundary  C enlarge boundary
147         do j=1,ny_in        do j=1,ny_in
148          arrayin(0,j)       = arrayin(nx_in,j)         arrayin(0,j)       = arrayin(nx_in,j)
149          arrayin(-1,j)      = arrayin(nx_in-1,j)         arrayin(-1,j)      = arrayin(nx_in-1,j)
150          arrayin(nx_in+1,j) = arrayin(1,j)         arrayin(nx_in+1,j) = arrayin(1,j)
151          arrayin(nx_in+2,j) = arrayin(2,j)         arrayin(nx_in+2,j) = arrayin(2,j)
152         enddo        enddo
153         do i=-1,nx_in+2        do i=-1,nx_in+2
154          arrayin(i,0)       = arrayin(i,1)         arrayin(i,0)       = arrayin(i,1)
155          arrayin(i,-1)      = arrayin(i,1)         arrayin(i,-1)      = arrayin(i,1)
156          arrayin(i,ny_in+1) = arrayin(i,ny_in)         arrayin(i,ny_in+1) = arrayin(i,ny_in)
157          arrayin(i,ny_in+2) = arrayin(i,ny_in)         arrayin(i,ny_in+2) = arrayin(i,ny_in)
158         enddo        enddo
159    
160  C     For tracer (method=1,2) set to northernmost zonal-mean value  C     For tracer (method=1,2) set to northernmost zonal-mean value
161  C     at 90N to avoid sharp zonal gradients near the Pole.  C     at 90N to avoid sharp zonal gradients near the Pole.
# Line 142  C     For U (method=11,12) set to zero a Line 163  C     For U (method=11,12) set to zero a
163  C     gradient at North Pole  C     gradient at North Pole
164  C     For V (method=11,12) set to northernmost zonal value at 90N,  C     For V (method=11,12) set to northernmost zonal value at 90N,
165  C     as is already done above in order to allow cross-PoleArctic flow  C     as is already done above in order to allow cross-PoleArctic flow
166         if (y_in(ny_in+1).eq.ninety) then        do j=ny_in,ny_in+2
167           if (y_in(j).eq.ninety) then
168          if (method.eq.1 .or. method.eq.2) then          if (method.eq.1 .or. method.eq.2) then
169           NorthValue = 0           NorthValue = 0.
170           do i=1,nx_in           do i=1,nx_in
171            NorthValue = NorthValue + arrayin(i,ny_in)            NorthValue = NorthValue + arrayin(i,j)
172           enddo           enddo
173           NorthValue = NorthValue / nx_in           NorthValue = NorthValue / nx_in
174           do i=-1,nx_in+2           do i=-1,nx_in+2
175            arrayin(i,ny_in+1) = NorthValue            arrayin(i,j) = NorthValue
176           enddo           enddo
177          elseif (method.eq.11 .or. method.eq.12) then          elseif (method.eq.11 .or. method.eq.12) then
178           do i=-1,nx_in+2           do i=-1,nx_in+2
179            arrayin(i,ny_in+1) = 0            arrayin(i,j) = 0.
          enddo  
         endif  
        endif  
        if (y_in(ny_in+2).eq.ninety) then  
         if (method.eq.1 .or. method.eq.2) then  
          NorthValue = 0  
          do i=1,nx_in  
           NorthValue = NorthValue + arrayin(i,ny_in)  
          enddo  
          NorthValue = NorthValue / nx_in  
          do i=-1,nx_in+2  
           arrayin(i,ny_in+2) = NorthValue  
          enddo  
         elseif (method.eq.11 .or. method.eq.12) then  
          do i=-1,nx_in+2  
           arrayin(i,ny_in+2) = 0  
180           enddo           enddo
181          endif          endif
182         endif         endif
183          enddo
184    
 C     _END_MASTER( myThid )  
         
185        do bj = mybylo(mythid), mybyhi(mythid)        do bj = mybylo(mythid), mybyhi(mythid)
186         do bi = mybxlo(mythid), mybxhi(mythid)         do bi = mybxlo(mythid), mybxhi(mythid)
187    
# Line 203  C check validity of input/output coordin Line 208  C check validity of input/output coordin
208          endif          endif
209  #endif /* ALLOW_DEBUG */  #endif /* ALLOW_DEBUG */
210    
211  C compute interpolation indices  C compute interpolation indices
212          do i=1,snx          do i=1,snx
213           do j=1,sny           do j=1,sny
214            if (xG(i,j,bi,bj)-x_in(1) .ge. 0.) then            if (xG(i,j,bi,bj)-x_in(1) .ge. 0.) then
# Line 212  C compute interpolation indices Line 217  C compute interpolation indices
217             w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc)             w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc)
218            endif            endif
219            e_ind(i,j) = w_ind(i,j) + 1            e_ind(i,j) = w_ind(i,j) + 1
220             enddo
221            enddo
222    #ifndef TARGET_NEC_SX
223    C     use the original and more readable variant of the algorithm that
224    C     has unvectorizable while-loops for each (i,j)
225            do i=1,snx
226             do j=1,sny
227            js = ny_in*.5            js = ny_in*.5
228            do while (yG(i,j,bi,bj) .lt. y_in(js))            do while (yG(i,j,bi,bj) .lt. y_in(js))
229             js = (js - 1)*.5             js = (js - 1)*.5
# Line 220  C compute interpolation indices Line 232  C compute interpolation indices
232             js = js + 1             js = js + 1
233            enddo            enddo
234            s_ind(i,j) = js            s_ind(i,j) = js
235            n_ind(i,j) = js + 1           enddo
236            enddo
237    #else /* TARGET_NEC_SX defined */
238    C     this variant vectorizes more efficiently than the original one because
239    C     it moves the while loops out of the i,j loops (loop pushing) but
240    C     it is ugly and incomprehensible
241            icnt = 0
242            do j=1,sny
243             do i=1,snx
244              s_ind(i,j) = ny_in*.5
245              icnt = icnt+1
246              inx(icnt,1) = i
247              inx(icnt,2) = j
248             enddo
249            enddo
250            do while (icnt .gt. 0)
251             ii = 0
252    !CDIR NODEP
253             do ic=1,icnt
254              i = inx(ic,1)
255              j = inx(ic,2)
256              if (yG(i,j,bi,bj) .lt. y_in(s_ind(i,j))) then
257               s_ind(i,j) = (s_ind(i,j) - 1)*.5
258               ii = ii+1
259               inx(ii,1) = i
260               inx(ii,2) = j
261              endif
262             enddo
263             icnt = ii
264            enddo
265            icnt = 0
266            do j=1,sny
267             do i=1,snx
268              icnt = icnt+1
269              inx(icnt,1) = i
270              inx(icnt,2) = j
271             enddo
272            enddo
273            do while (icnt .gt. 0)
274             ii = 0
275    !CDIR NODEP
276             do ic=1,icnt
277              i = inx(ic,1)
278              j = inx(ic,2)
279              if (yG(i,j,bi,bj) .ge. y_in(s_ind(i,j)+1)) then
280               s_ind(i,j) = s_ind(i,j) + 1
281               ii = ii+1
282               inx(ii,1) = i
283               inx(ii,2) = j
284              endif
285             enddo
286             icnt = ii
287            enddo
288    #endif /* TARGET_NEC_SX defined */
289            do i=1,snx
290             do j=1,sny
291              n_ind(i,j) = s_ind(i,j) + 1
292           enddo           enddo
293          enddo          enddo
294    
# Line 235  C bilinear interpolation Line 303  C bilinear interpolation
303              px_ind(l+1) = x_in(w_ind(i,j)+l)              px_ind(l+1) = x_in(w_ind(i,j)+l)
304              py_ind(l+1) = y_in(s_ind(i,j)+l)              py_ind(l+1) = y_in(s_ind(i,j)+l)
305             enddo             enddo
306    #ifndef TARGET_NEC_SX
307             do k=1,2             do k=1,2
308              ew_val(k) = arrayin(w_ind(i,j),s_ind(i,j)+k-1)              ew_val(k) = arrayin(w_ind(i,j),s_ind(i,j)+k-1)
309       &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)       &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)
# Line 243  C bilinear interpolation Line 312  C bilinear interpolation
312              arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)              arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
313       &             +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)       &             +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
314             enddo             enddo
315    #else
316               ew_val1 = arrayin(w_ind(i,j),s_ind(i,j)+1-1)
317         &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)
318         &             +arrayin(e_ind(i,j),s_ind(i,j)+1-1)
319         &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)
320               ew_val2 = arrayin(w_ind(i,j),s_ind(i,j)+2-1)
321         &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)
322         &             +arrayin(e_ind(i,j),s_ind(i,j)+2-1)
323         &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)
324               arrayout(i,j,bi,bj)=
325         &             +ew_val1*lagran(1,yG(i,j,bi,bj),py_ind,sp)
326         &             +ew_val2*lagran(2,yG(i,j,bi,bj),py_ind,sp)
327    #endif /* TARGET_NEC_SX defined */
328            enddo            enddo
329           enddo           enddo
330          elseif (method .eq. 2 .or. method.eq.12 .or. method.eq.22) then          elseif (method .eq. 2 .or. method.eq.12 .or. method.eq.22) then
# Line 256  C bicubic interpolation Line 338  C bicubic interpolation
338              px_ind(l+2) = x_in(w_ind(i,j)+l)              px_ind(l+2) = x_in(w_ind(i,j)+l)
339              py_ind(l+2) = y_in(s_ind(i,j)+l)              py_ind(l+2) = y_in(s_ind(i,j)+l)
340             enddo             enddo
341    #ifndef TARGET_NEC_SX
342             do k=1,4             do k=1,4
343              ew_val(k) =              ew_val(k) =
344       &             arrayin(w_ind(i,j)-1,s_ind(i,j)+k-2)       &             arrayin(w_ind(i,j)-1,s_ind(i,j)+k-2)
# Line 263  C bicubic interpolation Line 346  C bicubic interpolation
346       &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+k-2)       &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+k-2)
347       &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)       &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)
348       &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+k-2)       &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+k-2)
349       &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)       &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)
350       &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+k-2)       &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+k-2)
351       &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)       &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)
352              arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)              arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
353       &             +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)       &             +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
354             enddo             enddo
355    #else
356               ew_val1 =
357         &             arrayin(w_ind(i,j)-1,s_ind(i,j)+1-2)
358         &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)
359         &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+1-2)
360         &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)
361         &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+1-2)
362         &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)
363         &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+1-2)
364         &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)
365                ew_val2 =
366         &             arrayin(w_ind(i,j)-1,s_ind(i,j)+2-2)
367         &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)
368         &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+2-2)
369         &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)
370         &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+2-2)
371         &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)
372         &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+2-2)
373         &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)
374                ew_val3 =
375         &             arrayin(w_ind(i,j)-1,s_ind(i,j)+3-2)
376         &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)
377         &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+3-2)
378         &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)
379         &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+3-2)
380         &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)
381         &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+3-2)
382         &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)
383                ew_val4 =
384         &             arrayin(w_ind(i,j)-1,s_ind(i,j)+4-2)
385         &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)
386         &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+4-2)
387         &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)
388         &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+4-2)
389         &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)
390         &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+4-2)
391         &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)
392                arrayout(i,j,bi,bj)=
393         &             +ew_val1*lagran(1,yG(i,j,bi,bj),py_ind,sp)
394         &             +ew_val2*lagran(2,yG(i,j,bi,bj),py_ind,sp)
395         &             +ew_val3*lagran(3,yG(i,j,bi,bj),py_ind,sp)
396         &             +ew_val4*lagran(4,yG(i,j,bi,bj),py_ind,sp)
397    #endif /* TARGET_NEC_SX defined */
398            enddo            enddo
399           enddo           enddo
400          else          else
# Line 277  C bicubic interpolation Line 403  C bicubic interpolation
403         enddo         enddo
404        enddo        enddo
405    
406          RETURN
407        END        END

Legend:
Removed from v.1.16  
changed lines
  Added in v.1.23

  ViewVC Help
Powered by ViewVC 1.1.22