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

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

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


Revision 1.7 - (show annotations) (download)
Mon Mar 19 14:32:47 2012 UTC (12 years, 2 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63m, checkpoint63n
Changes since 1.6: +8 -4 lines
move k-loop outside of i/j-loops when (re-)computing R_low in
in order to avoid -O3 optimization problems with some compilers
(gfortran 4.6.0 on MacOS)

1 C $Header: /u/gcmpack/MITgcm/model/src/update_masks_etc.F,v 1.6 2011/06/08 01:21:14 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: UPDATE_MASKS_ETC
8 C !INTERFACE:
9 SUBROUTINE UPDATE_MASKS_ETC( myThid )
10 C !DESCRIPTION: \bv
11 C *==========================================================*
12 C | SUBROUTINE UPDATE_MASKS_ETC
13 C | o Re-initialise masks and topography factors after a new
14 C | hFacC has been calculated by the minimizer
15 C *==========================================================*
16 C | These arrays are used throughout the code and describe
17 C | the topography of the domain through masks (0s and 1s)
18 C | and fractional height factors (0<hFac<1). The latter
19 C | distinguish between the lopped-cell and full-step
20 C | topographic representations.
21 C *==========================================================*
22 C | code taken from ini_masks_etc.F
23 C *==========================================================*
24 C \ev
25
26 C !USES:
27 IMPLICIT NONE
28 C === Global variables ===
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "GRID.h"
33 #include "SURFACE.h"
34 Cml we need optimcycle for storing the new hFaC(C/W/S) and depth
35 #ifdef ALLOW_AUTODIFF_TAMC
36 # include "optim.h"
37 #endif
38
39 C !INPUT/OUTPUT PARAMETERS:
40 C == Routine arguments ==
41 C myThid - Number of this instance of INI_MASKS_ETC
42 INTEGER myThid
43
44 #ifdef ALLOW_DEPTH_CONTROL
45 C !LOCAL VARIABLES:
46 C == Local variables ==
47 C bi,bj :: Loop counters
48 C I,J,K
49 C tmpfld :: Temporary array used to compute & write Total Depth
50 INTEGER bi, bj
51 INTEGER I, J, K
52 _RS tmpfld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
53 CHARACTER*(MAX_LEN_MBUF) suff
54 Cml(
55 INTEGER Im1, Jm1
56 _RL hFacCtmp, hFacCtmp2
57 _RL hFacMnSz
58 _RS smoothMin_R4
59 EXTERNAL smoothMin_R4
60 Cml)
61 CEOP
62
63 C- Calculate lopping factor hFacC : over-estimate the part inside of the domain
64 C taking into account the lower_R Boundary (Bathymetrie / Top of Atmos)
65 DO bj=myByLo(myThid), myByHi(myThid)
66 DO bi=myBxLo(myThid), myBxHi(myThid)
67 DO K=1, Nr
68 hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
69 DO J=1-Oly,sNy+Oly
70 DO I=1-Olx,sNx+Olx
71 C o Non-dimensional distance between grid bound. and domain lower_R bound.
72 #ifdef ALLOW_DEPTH_CONTROL
73 hFacCtmp = (rF(K)-xx_r_low(I,J,bi,bj))*recip_drF(K)
74 #else
75 hFacCtmp = (rF(K)-R_low(I,J,bi,bj))*recip_drF(K)
76 #endif /* ALLOW_DEPTH_CONTROL */
77 Cml IF ( hFacCtmp .le. 0. _d 0 ) THEN
78 CmlC IF ( hFacCtmp .lt. 0.5*hfacMnSz ) THEN
79 Cml hFacCtmp2 = 0. _d 0
80 Cml ELSE
81 Cml hFacCtmp2 = hFacCtmp + hFacMnSz*(
82 Cml & EXP(-hFacCtmp/hFacMnSz)-EXP(-1./hFacMnSz) )
83 Cml ENDIF
84 Cml call limit_hfacc_to_one( hFacCtmp2 )
85 Cml hFacC(I,J,K,bi,bj) = hFacCtmp2
86 IF ( hFacCtmp .le. 0. _d 0 ) THEN
87 C IF ( hFacCtmp .lt. 0.5*hfacMnSz ) THEN
88 hFacC(I,J,K,bi,bj) = 0. _d 0
89 ELSEIF ( hFacCtmp .gt. 1. _d 0 ) THEN
90 hFacC(I,J,K,bi,bj) = 1. _d 0
91 ELSE
92 hFacC(I,J,K,bi,bj) = hFacCtmp + hFacMnSz*(
93 & EXP(-hFacCtmp/hFacMnSz)-EXP(-1./hFacMnSz) )
94 ENDIF
95 Cml print '(A,3I5,F20.16)', 'ml-hfac:', I,J,K,hFacC(I,J,K,bi,bj)
96 CmlC o Select between, closed, open or partial (0,1,0-1)
97 Cml hFacCtmp=min( max( hFacCtmp, 0. _d 0) , 1. _d 0)
98 CmlC o Impose minimum fraction and/or size (dimensional)
99 Cml IF (hFacCtmp.LT.hFacMnSz) THEN
100 Cml IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
101 Cml hFacC(I,J,K,bi,bj)=0.
102 Cml ELSE
103 Cml hFacC(I,J,K,bi,bj)=hFacMnSz
104 Cml ENDIF
105 Cml ELSE
106 Cml hFacC(I,J,K,bi,bj)=hFacCtmp
107 Cml ENDIF
108 Cml ENDIF
109 Cml print '(A,F15.4,F20.16)', 'ml-hfac:', R_low(i,j,bi,bj),hFacC(I,J,K,bi,bj)
110 ENDDO
111 ENDDO
112 ENDDO
113 C - end bi,bj loops.
114 ENDDO
115 ENDDO
116 C
117 C _EXCH_XYZ_RS(hFacC,myThid)
118 C
119 C- Re-calculate lower-R Boundary position, taking into account hFacC
120 DO bj=myByLo(myThid), myByHi(myThid)
121 DO bi=myBxLo(myThid), myBxHi(myThid)
122 DO J=1-Oly,sNy+Oly
123 DO I=1-Olx,sNx+Olx
124 R_low(i,j,bi,bj) = rF(1)
125 ENDDO
126 ENDDO
127 DO K=Nr,1,-1
128 DO J=1-Oly,sNy+Oly
129 DO I=1-Olx,sNx+Olx
130 R_low(I,J,bi,bj) = R_low(I,J,bi,bj)
131 & - drF(K)*hFacC(I,J,K,bi,bj)
132 ENDDO
133 ENDDO
134 ENDDO
135 C - end bi,bj loops.
136 ENDDO
137 ENDDO
138 C
139
140 Cml DO bj=myByLo(myThid), myByHi(myThid)
141 Cml DO bi=myBxLo(myThid), myBxHi(myThid)
142 CmlC- Re-calculate Reference surface position, taking into account hFacC
143 CmlC initialize Total column fluid thickness and surface k index
144 CmlC Note: if no fluid (continent) ==> ksurf = Nr+1
145 Cml DO J=1-Oly,sNy+Oly
146 Cml DO I=1-Olx,sNx+Olx
147 Cml tmpfld(I,J,bi,bj) = 0.
148 Cml ksurfC(I,J,bi,bj) = Nr+1
149 Cml Ro_surf(I,J,bi,bj) = R_low(I,J,bi,bj)
150 Cml DO K=Nr,1,-1
151 Cml Ro_surf(I,J,bi,bj) = Ro_surf(I,J,bi,bj)
152 Cml & + drF(k)*hFacC(I,J,K,bi,bj)
153 Cml IF (maskC(I,J,K,bi,bj).NE.0.) THEN
154 Cml ksurfC(I,J,bi,bj) = k
155 Cml tmpfld(i,j,bi,bj) = tmpfld(i,j,bi,bj) + 1.
156 Cml ENDIF
157 Cml ENDDO
158 Cml ENDDO
159 Cml ENDDO
160 CmlC - end bi,bj loops.
161 Cml ENDDO
162 Cml ENDDO
163
164 IF ( debugLevel.GE.debLevC ) THEN
165 _BARRIER
166 CALL PLOT_FIELD_XYRS( R_low,
167 & 'Model R_low (update_masks_etc)', 1, myThid )
168 CML I assume that Ro_surf is not changed anywhere else in the code
169 CML and since it is not changed in this routine, we do not need to
170 CML print it again.
171 CML CALL PLOT_FIELD_XYRS( Ro_surf,
172 CML & 'Model Ro_surf (update_masks_etc)', 1, myThid )
173 ENDIF
174
175 C Calculate quantities derived from XY depth map
176 DO bj = myByLo(myThid), myByHi(myThid)
177 DO bi = myBxLo(myThid), myBxHi(myThid)
178 DO j=1-Oly,sNy+Oly
179 DO i=1-Olx,sNx+Olx
180 C Total fluid column thickness (r_unit) :
181 tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
182 C Inverse of fluid column thickness (1/r_unit)
183 IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
184 recip_Rcol(i,j,bi,bj) = 0.
185 ELSE
186 recip_Rcol(i,j,bi,bj) = 1. _d 0 / tmpfld(i,j,bi,bj)
187 ENDIF
188 ENDDO
189 ENDDO
190 ENDDO
191 ENDDO
192 C _EXCH_XY_RS( recip_Rcol, myThid )
193
194 C hFacW and hFacS (at U and V points)
195 CML This will be the crucial part of the code, because here the minimum
196 CML function MIN is involved which does not have a continuous derivative
197 CML for MIN(x,y) at y=x.
198 CML The thin walls representation has been moved into this loop, that is
199 CML before the call to EXCH_UV_XVY_RS, because TAMC will prefer it this
200 CML way. On the other hand, this might cause difficulties in some
201 CML configurations.
202 DO bj=myByLo(myThid), myByHi(myThid)
203 DO bi=myBxLo(myThid), myBxHi(myThid)
204 DO K=1, Nr
205 CML DO J=1-Oly+1,sNy+Oly
206 CML DO I=1-Olx+1,sNx+Olx
207 CML DO J=1,sNy+1
208 CML DO I=1,sNx+1
209 DO J=1-Oly,sNy+Oly
210 DO I=1-Olx,sNx+Olx
211 Im1=MAX(I-1,1-OLx)
212 Jm1=MAX(J-1,1-OLy)
213 IF (DYG(I,J,bi,bj).EQ.0.) THEN
214 C thin walls representation of non-periodic
215 C boundaries such as happen on the lat-lon grid at the N/S poles.
216 C We should really supply a flag for doing this.
217 hFacW(I,J,K,bi,bj)=0.
218 ELSE
219 Cml hFacW(I,J,K,bi,bj)=
220 hFacW(I,J,K,bi,bj)=maskW(I,J,K,bi,bj)*
221 #ifdef USE_SMOOTH_MIN
222 & smoothMin_R4(hFacC(I,J,K,bi,bj),hFacC(Im1,J,K,bi,bj))
223 #else
224 & MIN(hFacC(I,J,K,bi,bj),hFacC(Im1,J,K,bi,bj))
225 #endif /* USE_SMOOTH_MIN */
226 ENDIF
227 IF (DXG(I,J,bi,bj).EQ.0.) THEN
228 hFacS(I,J,K,bi,bj)=0.
229 ELSE
230 Cml hFacS(I,J,K,bi,bj)=
231 hFacS(I,J,K,bi,bj)=maskS(I,J,K,bi,bj)*
232 #ifdef USE_SMOOTH_MIN
233 & smoothMin_R4(hFacC(I,J,K,bi,bj),hFacC(I,Jm1,K,bi,bj))
234 #else
235 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,Jm1,K,bi,bj))
236 #endif /* USE_SMOOTH_MIN */
237 ENDIF
238 ENDDO
239 ENDDO
240 ENDDO
241 ENDDO
242 ENDDO
243 #if (defined (ALLOW_AUTODIFF_TAMC) && \
244 defined (ALLOW_AUTODIFF_MONITOR) && \
245 defined (ALLOW_DEPTH_CONTROL))
246 C Include call to a dummy routine. Its adjoint will be
247 C called at the proper place in the adjoint code.
248 C The adjoint routine will print out adjoint values
249 C if requested. The location of the call is important,
250 C it has to be after the adjoint of the exchanges
251 C (DO_GTERM_BLOCKING_EXCHANGES).
252 Cml CALL DUMMY_IN_HFAC( 'W', 0, myThid )
253 Cml CALL DUMMY_IN_HFAC( 'S', 0, myThid )
254 #endif
255 Cml CALL EXCH_UV_XYZ_RL(hFacW,hFacS,.FALSE.,myThid)
256 CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
257 #if (defined (ALLOW_AUTODIFF_TAMC) && \
258 defined (ALLOW_AUTODIFF_MONITOR) && \
259 defined (ALLOW_DEPTH_CONTROL))
260 C Include call to a dummy routine. Its adjoint will be
261 C called at the proper place in the adjoint code.
262 C The adjoint routine will print out adjoint values
263 C if requested. The location of the call is important,
264 C it has to be after the adjoint of the exchanges
265 C (DO_GTERM_BLOCKING_EXCHANGES).
266 Cml CALL DUMMY_IN_HFAC( 'W', 1, myThid )
267 Cml CALL DUMMY_IN_HFAC( 'S', 1, myThid )
268 #endif
269
270 C- Write to disk: Total Column Thickness & hFac(C,W,S):
271 WRITE(suff,'(I10.10)') optimcycle
272 CALL WRITE_FLD_XY_RS( 'Depth.',suff,tmpfld,optimcycle,myThid)
273 CALL WRITE_FLD_XYZ_RS( 'hFacC.',suff,hFacC,optimcycle,myThid)
274 CALL WRITE_FLD_XYZ_RS( 'hFacW.',suff,hFacW,optimcycle,myThid)
275 CALL WRITE_FLD_XYZ_RS( 'hFacS.',suff,hFacS,optimcycle,myThid)
276
277 IF ( debugLevel.GE.debLevC ) THEN
278 _BARRIER
279 C-- Write to monitor file (standard output)
280 CALL PLOT_FIELD_XYZRS( hFacC,'hFacC (update_masks_etc)',
281 & Nr, 1, myThid )
282 CALL PLOT_FIELD_XYZRS( hFacW,'hFacW (update_masks_etc)',
283 & Nr, 1, myThid )
284 CALL PLOT_FIELD_XYZRS( hFacS,'hFacS (update_masks_etc)',
285 & Nr, 1, myThid )
286 ENDIF
287
288 C Masks and reciprocals of hFac[CWS]
289 Cml The masks should stay constant, so they are not recomputed at this time
290 Cml implicitly implying that no cell that is wet in the begin will ever dry
291 Cml up! This is a strong constraint and should be implementent as a hard
292 Cml inequality contraint when performing optimization (m1qn3 cannot do that)
293 Cml Also, I am assuming here that the new hFac(s) never become zero during
294 Cml optimization!
295 DO bj = myByLo(myThid), myByHi(myThid)
296 DO bi = myBxLo(myThid), myBxHi(myThid)
297 DO K=1,Nr
298 DO J=1-Oly,sNy+Oly
299 DO I=1-Olx,sNx+Olx
300 IF (hFacC(I,J,K,bi,bj) .NE. 0. ) THEN
301 Cml IF (maskC(I,J,K,bi,bj) .NE. 0. ) THEN
302 recip_hFacC(I,J,K,bi,bj) = 1. _d 0 / hFacC(I,J,K,bi,bj)
303 Cml maskC(I,J,K,bi,bj) = 1.
304 ELSE
305 recip_hFacC(I,J,K,bi,bj) = 0.
306 Cml maskC(I,J,K,bi,bj) = 0.
307 ENDIF
308 IF (hFacW(I,J,K,bi,bj) .NE. 0. ) THEN
309 Cml IF (maskW(I,J,K,bi,bj) .NE. 0. ) THEN
310 recip_hFacW(I,J,K,bi,bj) = 1. _d 0 / hFacw(I,J,K,bi,bj)
311 Cml maskW(I,J,K,bi,bj) = 1.
312 ELSE
313 recip_hFacW(I,J,K,bi,bj) = 0.
314 Cml maskW(I,J,K,bi,bj) = 0.
315 ENDIF
316 IF (hFacS(I,J,K,bi,bj) .NE. 0. ) THEN
317 Cml IF (maskS(I,J,K,bi,bj) .NE. 0. ) THEN
318 recip_hFacS(I,J,K,bi,bj) = 1. _d 0 / hFacS(I,J,K,bi,bj)
319 Cml maskS(I,J,K,bi,bj) = 1.
320 ELSE
321 recip_hFacS(I,J,K,bi,bj) = 0.
322 Cml maskS(I,J,K,bi,bj) = 0.
323 ENDIF
324 ENDDO
325 ENDDO
326 ENDDO
327 CmlCml(
328 Cml ENDDO
329 Cml ENDDO
330 Cml _EXCH_XYZ_RS(recip_hFacC , myThid )
331 Cml _EXCH_XYZ_RS(recip_hFacW , myThid )
332 Cml _EXCH_XYZ_RS(recip_hFacS , myThid )
333 Cml _EXCH_XYZ_RS(maskC , myThid )
334 Cml _EXCH_XYZ_RS(maskW , myThid )
335 Cml _EXCH_XYZ_RS(maskS , myThid )
336 Cml DO bj = myByLo(myThid), myByHi(myThid)
337 Cml DO bi = myBxLo(myThid), myBxHi(myThid)
338 CmlCml)
339 C- Calculate surface k index for interface W & S (U & V points)
340 DO J=1-Oly,sNy+Oly
341 DO I=1-Olx,sNx+Olx
342 ksurfW(I,J,bi,bj) = Nr+1
343 ksurfS(I,J,bi,bj) = Nr+1
344 DO k=Nr,1,-1
345 Cml IF (hFacW(I,J,K,bi,bj).NE.0.) THEN
346 IF (maskW(I,J,K,bi,bj).NE.0.) THEN
347 ksurfW(I,J,bi,bj) = k
348 ENDIF
349 Cml IF (hFacS(I,J,K,bi,bj).NE.0.) THEN
350 IF (maskS(I,J,K,bi,bj).NE.0.) THEN
351 ksurfS(I,J,bi,bj) = k
352
353 ENDIF
354 ENDDO
355 ENDDO
356 ENDDO
357 C - end bi,bj loops.
358 ENDDO
359 ENDDO
360
361 c #ifdef ALLOW_NONHYDROSTATIC
362 C-- Calculate "recip_hFacU" = reciprocal hfac distance/volume for W cells
363 C not used ; computed locally in CALC_GW
364 c #endif
365
366 #endif /* ALLOW_DEPTH_CONTROL */
367 RETURN
368 END
369
370 #ifdef USE_SMOOTH_MIN
371 _RS function smoothMin_R4( a, b )
372
373 implicit none
374
375 _RS a, b
376
377 _RS smoothAbs_R4
378 external smoothAbs_R4
379
380 Cml smoothMin_R4 = .5*(a+b)
381 smoothMin_R4 = .5*( a+b - smoothAbs_R4(a-b) )
382 CML smoothMin_R4 = MIN(a,b)
383
384 return
385 end
386
387 _RL function smoothMin_R8( a, b )
388
389 implicit none
390
391 _RL a, b
392
393 _RL smoothAbs_R8
394 external smoothAbs_R8
395
396 Cml smoothMin_R8 = .5*(a+b)
397 smoothMin_R8 = .5*( a+b - smoothAbs_R8(a-b) )
398 Cml smoothMin_R8 = MIN(a,b)
399
400 return
401 end
402
403 _RS function smoothAbs_R4( x )
404
405 implicit none
406 C === Global variables ===
407 #include "SIZE.h"
408 #include "EEPARAMS.h"
409 #include "PARAMS.h"
410 C input parameter
411 _RS x
412 c local variable
413 _RS sf, rsf
414
415 if ( smoothAbsFuncRange .lt. 0.0 ) then
416 c limit of smoothMin(a,b) = .5*(a+b)
417 smoothAbs_R4 = 0.
418 else
419 if ( smoothAbsFuncRange .ne. 0.0 ) then
420 sf = 10.0/smoothAbsFuncRange
421 rsf = 1./sf
422 else
423 c limit of smoothMin(a,b) = min(a,b)
424 sf = 0.
425 rsf = 0.
426 end if
427 c
428 if ( x .gt. smoothAbsFuncRange ) then
429 smoothAbs_R4 = x
430 else if ( x .lt. -smoothAbsFuncRange ) then
431 smoothAbs_R4 = -x
432 else
433 smoothAbs_R4 = log(.5*(exp(x*sf)+exp(-x*sf)))*rsf
434 end if
435 end if
436
437 return
438 end
439
440 _RL function smoothAbs_R8( x )
441
442 implicit none
443 C === Global variables ===
444 #include "SIZE.h"
445 #include "EEPARAMS.h"
446 #include "PARAMS.h"
447 C input parameter
448 _RL x
449 c local variable
450 _RL sf, rsf
451
452 if ( smoothAbsFuncRange .lt. 0.0 ) then
453 c limit of smoothMin(a,b) = .5*(a+b)
454 smoothAbs_R8 = 0.
455 else
456 if ( smoothAbsFuncRange .ne. 0.0 ) then
457 sf = 10.0D0/smoothAbsFuncRange
458 rsf = 1.D0/sf
459 else
460 c limit of smoothMin(a,b) = min(a,b)
461 sf = 0.D0
462 rsf = 0.D0
463 end if
464 c
465 if ( x .ge. smoothAbsFuncRange ) then
466 smoothAbs_R8 = x
467 else if ( x .le. -smoothAbsFuncRange ) then
468 smoothAbs_R8 = -x
469 else
470 smoothAbs_R8 = log(.5*(exp(x*sf)+exp(-x*sf)))*rsf
471 end if
472 end if
473
474 return
475 end
476 #endif /* USE_SMOOTH_MIN */
477
478 Cml#ifdef ALLOW_DEPTH_CONTROL
479 Cmlcadj SUBROUTINE limit_hfacc_to_one INPUT = 1
480 Cmlcadj SUBROUTINE limit_hfacc_to_one OUTPUT = 1
481 Cmlcadj SUBROUTINE limit_hfacc_to_one ACTIVE = 1
482 Cmlcadj SUBROUTINE limit_hfacc_to_one DEPEND = 1
483 Cmlcadj SUBROUTINE limit_hfacc_to_one REQUIRED
484 Cmlcadj SUBROUTINE limit_hfacc_to_one ADNAME = adlimit_hfacc_to_one
485 Cml#endif /* ALLOW_DEPTH_CONTROL */
486 Cml subroutine limit_hfacc_to_one( hf )
487 Cml
488 Cml _RL hf
489 Cml
490 Cml if ( hf .gt. 1. _d 0 ) then
491 Cml hf = 1. _d 0
492 Cml endif
493 Cml
494 Cml return
495 Cml end
496 Cml
497 Cml subroutine adlimit_hfacc_to_one( hf, adhf )
498 Cml
499 Cml _RL hf, adhf
500 Cml
501 Cml return
502 Cml end
503
504 #ifdef ALLOW_DEPTH_CONTROL
505 cadj SUBROUTINE dummy_in_hfac INPUT = 1, 2, 3
506 cadj SUBROUTINE dummy_in_hfac OUTPUT =
507 cadj SUBROUTINE dummy_in_hfac ACTIVE =
508 cadj SUBROUTINE dummy_in_hfac DEPEND = 1, 2, 3
509 cadj SUBROUTINE dummy_in_hfac REQUIRED
510 cadj SUBROUTINE dummy_in_hfac INFLUENCED
511 cadj SUBROUTINE dummy_in_hfac ADNAME = addummy_in_hfac
512 cadj SUBROUTINE dummy_in_hfac FTLNAME = g_dummy_in_hfac
513 #endif /* ALLOW_DEPTH_CONTROL */
514

  ViewVC Help
Powered by ViewVC 1.1.22