/[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.5 - (show annotations) (download)
Sun May 9 22:40:03 2010 UTC (14 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62g, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62y, checkpoint62x
Changes since 1.4: +40 -36 lines
call PLOT_FIELD if debugLevel.GE.debLevB ; fix for multi-threaded (IO).

1 C $Header: /u/gcmpack/MITgcm/model/src/update_masks_etc.F,v 1.4 2010/03/16 00:08:27 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 DO K=Nr,1,-1
126 R_low(I,J,bi,bj) = R_low(I,J,bi,bj)
127 & - drF(k)*hFacC(I,J,K,bi,bj)
128 ENDDO
129 ENDDO
130 ENDDO
131 C - end bi,bj loops.
132 ENDDO
133 ENDDO
134 C
135
136 Cml DO bj=myByLo(myThid), myByHi(myThid)
137 Cml DO bi=myBxLo(myThid), myBxHi(myThid)
138 CmlC- Re-calculate Reference surface position, taking into account hFacC
139 CmlC initialize Total column fluid thickness and surface k index
140 CmlC Note: if no fluid (continent) ==> ksurf = Nr+1
141 Cml DO J=1-Oly,sNy+Oly
142 Cml DO I=1-Olx,sNx+Olx
143 Cml tmpfld(I,J,bi,bj) = 0.
144 Cml ksurfC(I,J,bi,bj) = Nr+1
145 Cml Ro_surf(I,J,bi,bj) = R_low(I,J,bi,bj)
146 Cml DO K=Nr,1,-1
147 Cml Ro_surf(I,J,bi,bj) = Ro_surf(I,J,bi,bj)
148 Cml & + drF(k)*hFacC(I,J,K,bi,bj)
149 Cml IF (maskC(I,J,K,bi,bj).NE.0.) THEN
150 Cml ksurfC(I,J,bi,bj) = k
151 Cml tmpfld(i,j,bi,bj) = tmpfld(i,j,bi,bj) + 1.
152 Cml ENDIF
153 Cml ENDDO
154 Cml ENDDO
155 Cml ENDDO
156 CmlC - end bi,bj loops.
157 Cml ENDDO
158 Cml ENDDO
159
160 IF ( debugLevel.GE.debLevB ) THEN
161 _BARRIER
162 CALL PLOT_FIELD_XYRS( R_low,
163 & 'Model R_low (update_masks_etc)', 1, myThid )
164 CML I assume that Ro_surf is not changed anywhere else in the code
165 CML and since it is not changed in this routine, we do not need to
166 CML print it again.
167 CML CALL PLOT_FIELD_XYRS( Ro_surf,
168 CML & 'Model Ro_surf (update_masks_etc)', 1, myThid )
169 ENDIF
170
171 C Calculate quantities derived from XY depth map
172 DO bj = myByLo(myThid), myByHi(myThid)
173 DO bi = myBxLo(myThid), myBxHi(myThid)
174 DO j=1-Oly,sNy+Oly
175 DO i=1-Olx,sNx+Olx
176 C Total fluid column thickness (r_unit) :
177 tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
178 C Inverse of fluid column thickness (1/r_unit)
179 IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
180 recip_Rcol(i,j,bi,bj) = 0.
181 ELSE
182 recip_Rcol(i,j,bi,bj) = 1. _d 0 / tmpfld(i,j,bi,bj)
183 ENDIF
184 ENDDO
185 ENDDO
186 ENDDO
187 ENDDO
188 C _EXCH_XY_RS( recip_Rcol, myThid )
189
190 C hFacW and hFacS (at U and V points)
191 CML This will be the crucial part of the code, because here the minimum
192 CML function MIN is involved which does not have a continuous derivative
193 CML for MIN(x,y) at y=x.
194 CML The thin walls representation has been moved into this loop, that is
195 CML before the call to EXCH_UV_XVY_RS, because TAMC will prefer it this
196 CML way. On the other hand, this might cause difficulties in some
197 CML configurations.
198 DO bj=myByLo(myThid), myByHi(myThid)
199 DO bi=myBxLo(myThid), myBxHi(myThid)
200 DO K=1, Nr
201 CML DO J=1-Oly+1,sNy+Oly
202 CML DO I=1-Olx+1,sNx+Olx
203 CML DO J=1,sNy+1
204 CML DO I=1,sNx+1
205 DO J=1-Oly,sNy+Oly
206 DO I=1-Olx,sNx+Olx
207 Im1=MAX(I-1,1-OLx)
208 Jm1=MAX(J-1,1-OLy)
209 IF (DYG(I,J,bi,bj).EQ.0.) THEN
210 C thin walls representation of non-periodic
211 C boundaries such as happen on the lat-lon grid at the N/S poles.
212 C We should really supply a flag for doing this.
213 hFacW(I,J,K,bi,bj)=0.
214 ELSE
215 Cml hFacW(I,J,K,bi,bj)=
216 hFacW(I,J,K,bi,bj)=maskW(I,J,K,bi,bj)*
217 #ifdef USE_SMOOTH_MIN
218 & smoothMin_R4(hFacC(I,J,K,bi,bj),hFacC(Im1,J,K,bi,bj))
219 #else
220 & MIN(hFacC(I,J,K,bi,bj),hFacC(Im1,J,K,bi,bj))
221 #endif /* USE_SMOOTH_MIN */
222 ENDIF
223 IF (DXG(I,J,bi,bj).EQ.0.) THEN
224 hFacS(I,J,K,bi,bj)=0.
225 ELSE
226 Cml hFacS(I,J,K,bi,bj)=
227 hFacS(I,J,K,bi,bj)=maskS(I,J,K,bi,bj)*
228 #ifdef USE_SMOOTH_MIN
229 & smoothMin_R4(hFacC(I,J,K,bi,bj),hFacC(I,Jm1,K,bi,bj))
230 #else
231 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,Jm1,K,bi,bj))
232 #endif /* USE_SMOOTH_MIN */
233 ENDIF
234 ENDDO
235 ENDDO
236 ENDDO
237 ENDDO
238 ENDDO
239 #if (defined (ALLOW_AUTODIFF_TAMC) && \
240 defined (ALLOW_AUTODIFF_MONITOR) && \
241 defined (ALLOW_DEPTH_CONTROL))
242 C Include call to a dummy routine. Its adjoint will be
243 C called at the proper place in the adjoint code.
244 C The adjoint routine will print out adjoint values
245 C if requested. The location of the call is important,
246 C it has to be after the adjoint of the exchanges
247 C (DO_GTERM_BLOCKING_EXCHANGES).
248 Cml CALL DUMMY_IN_HFAC( 'W', 0, myThid )
249 Cml CALL DUMMY_IN_HFAC( 'S', 0, myThid )
250 #endif
251 Cml CALL EXCH_UV_XYZ_RL(hFacW,hFacS,.FALSE.,myThid)
252 CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
253 #if (defined (ALLOW_AUTODIFF_TAMC) && \
254 defined (ALLOW_AUTODIFF_MONITOR) && \
255 defined (ALLOW_DEPTH_CONTROL))
256 C Include call to a dummy routine. Its adjoint will be
257 C called at the proper place in the adjoint code.
258 C The adjoint routine will print out adjoint values
259 C if requested. The location of the call is important,
260 C it has to be after the adjoint of the exchanges
261 C (DO_GTERM_BLOCKING_EXCHANGES).
262 Cml CALL DUMMY_IN_HFAC( 'W', 1, myThid )
263 Cml CALL DUMMY_IN_HFAC( 'S', 1, myThid )
264 #endif
265
266 C- Write to disk: Total Column Thickness & hFac(C,W,S):
267 WRITE(suff,'(I10.10)') optimcycle
268 CALL WRITE_FLD_XY_RS( 'Depth.',suff,tmpfld,optimcycle,myThid)
269 CALL WRITE_FLD_XYZ_RS( 'hFacC.',suff,hFacC,optimcycle,myThid)
270 CALL WRITE_FLD_XYZ_RS( 'hFacW.',suff,hFacW,optimcycle,myThid)
271 CALL WRITE_FLD_XYZ_RS( 'hFacS.',suff,hFacS,optimcycle,myThid)
272
273 IF ( debugLevel.GE.debLevB ) THEN
274 _BARRIER
275 C-- Write to monitor file (standard output)
276 CALL PLOT_FIELD_XYZRS( hFacC,'hFacC (update_masks_etc)',
277 & Nr, 1, myThid )
278 CALL PLOT_FIELD_XYZRS( hFacW,'hFacW (update_masks_etc)',
279 & Nr, 1, myThid )
280 CALL PLOT_FIELD_XYZRS( hFacS,'hFacS (update_masks_etc)',
281 & Nr, 1, myThid )
282 ENDIF
283
284 C Masks and reciprocals of hFac[CWS]
285 Cml The masks should stay constant, so they are not recomputed at this time
286 Cml implicitly implying that no cell that is wet in the begin will ever dry
287 Cml up! This is a strong constraint and should be implementent as a hard
288 Cml inequality contraint when performing optimization (m1qn3 cannot do that)
289 Cml Also, I am assuming here that the new hFac(s) never become zero during
290 Cml optimization!
291 DO bj = myByLo(myThid), myByHi(myThid)
292 DO bi = myBxLo(myThid), myBxHi(myThid)
293 DO K=1,Nr
294 DO J=1-Oly,sNy+Oly
295 DO I=1-Olx,sNx+Olx
296 IF (hFacC(I,J,K,bi,bj) .NE. 0. ) THEN
297 Cml IF (maskC(I,J,K,bi,bj) .NE. 0. ) THEN
298 recip_hFacC(I,J,K,bi,bj) = 1. _d 0 / hFacC(I,J,K,bi,bj)
299 Cml maskC(I,J,K,bi,bj) = 1.
300 ELSE
301 recip_hFacC(I,J,K,bi,bj) = 0.
302 Cml maskC(I,J,K,bi,bj) = 0.
303 ENDIF
304 IF (hFacW(I,J,K,bi,bj) .NE. 0. ) THEN
305 Cml IF (maskW(I,J,K,bi,bj) .NE. 0. ) THEN
306 recip_hFacW(I,J,K,bi,bj) = 1. _d 0 / hFacw(I,J,K,bi,bj)
307 Cml maskW(I,J,K,bi,bj) = 1.
308 ELSE
309 recip_hFacW(I,J,K,bi,bj) = 0.
310 Cml maskW(I,J,K,bi,bj) = 0.
311 ENDIF
312 IF (hFacS(I,J,K,bi,bj) .NE. 0. ) THEN
313 Cml IF (maskS(I,J,K,bi,bj) .NE. 0. ) THEN
314 recip_hFacS(I,J,K,bi,bj) = 1. _d 0 / hFacS(I,J,K,bi,bj)
315 Cml maskS(I,J,K,bi,bj) = 1.
316 ELSE
317 recip_hFacS(I,J,K,bi,bj) = 0.
318 Cml maskS(I,J,K,bi,bj) = 0.
319 ENDIF
320 ENDDO
321 ENDDO
322 ENDDO
323 CmlCml(
324 Cml ENDDO
325 Cml ENDDO
326 Cml _EXCH_XYZ_RS(recip_hFacC , myThid )
327 Cml _EXCH_XYZ_RS(recip_hFacW , myThid )
328 Cml _EXCH_XYZ_RS(recip_hFacS , myThid )
329 Cml _EXCH_XYZ_RS(maskC , myThid )
330 Cml _EXCH_XYZ_RS(maskW , myThid )
331 Cml _EXCH_XYZ_RS(maskS , myThid )
332 Cml DO bj = myByLo(myThid), myByHi(myThid)
333 Cml DO bi = myBxLo(myThid), myBxHi(myThid)
334 CmlCml)
335 C- Calculate surface k index for interface W & S (U & V points)
336 DO J=1-Oly,sNy+Oly
337 DO I=1-Olx,sNx+Olx
338 ksurfW(I,J,bi,bj) = Nr+1
339 ksurfS(I,J,bi,bj) = Nr+1
340 DO k=Nr,1,-1
341 Cml IF (hFacW(I,J,K,bi,bj).NE.0.) THEN
342 IF (maskW(I,J,K,bi,bj).NE.0.) THEN
343 ksurfW(I,J,bi,bj) = k
344 ENDIF
345 Cml IF (hFacS(I,J,K,bi,bj).NE.0.) THEN
346 IF (maskS(I,J,K,bi,bj).NE.0.) THEN
347 ksurfS(I,J,bi,bj) = k
348
349 ENDIF
350 ENDDO
351 ENDDO
352 ENDDO
353 C - end bi,bj loops.
354 ENDDO
355 ENDDO
356
357 c #ifdef ALLOW_NONHYDROSTATIC
358 C-- Calculate "recip_hFacU" = reciprocal hfac distance/volume for W cells
359 C not used ; computed locally in CALC_GW
360 c #endif
361
362 #endif /* ALLOW_DEPTH_CONTROL */
363 RETURN
364 END
365
366 #ifdef USE_SMOOTH_MIN
367 _RS function smoothMin_R4( a, b )
368
369 implicit none
370
371 _RS a, b
372
373 _RS smoothAbs_R4
374 external smoothAbs_R4
375
376 Cml smoothMin_R4 = .5*(a+b)
377 smoothMin_R4 = .5*( a+b - smoothAbs_R4(a-b) )
378 CML smoothMin_R4 = MIN(a,b)
379
380 return
381 end
382
383 _RL function smoothMin_R8( a, b )
384
385 implicit none
386
387 _RL a, b
388
389 _RL smoothAbs_R8
390 external smoothAbs_R8
391
392 Cml smoothMin_R8 = .5*(a+b)
393 smoothMin_R8 = .5*( a+b - smoothAbs_R8(a-b) )
394 Cml smoothMin_R8 = MIN(a,b)
395
396 return
397 end
398
399 _RS function smoothAbs_R4( x )
400
401 implicit none
402 C === Global variables ===
403 #include "SIZE.h"
404 #include "EEPARAMS.h"
405 #include "PARAMS.h"
406 C input parameter
407 _RS x
408 c local variable
409 _RS sf, rsf
410
411 if ( smoothAbsFuncRange .lt. 0.0 ) then
412 c limit of smoothMin(a,b) = .5*(a+b)
413 smoothAbs_R4 = 0.
414 else
415 if ( smoothAbsFuncRange .ne. 0.0 ) then
416 sf = 10.0/smoothAbsFuncRange
417 rsf = 1./sf
418 else
419 c limit of smoothMin(a,b) = min(a,b)
420 sf = 0.
421 rsf = 0.
422 end if
423 c
424 if ( x .gt. smoothAbsFuncRange ) then
425 smoothAbs_R4 = x
426 else if ( x .lt. -smoothAbsFuncRange ) then
427 smoothAbs_R4 = -x
428 else
429 smoothAbs_R4 = log(.5*(exp(x*sf)+exp(-x*sf)))*rsf
430 end if
431 end if
432
433 return
434 end
435
436 _RL function smoothAbs_R8( x )
437
438 implicit none
439 C === Global variables ===
440 #include "SIZE.h"
441 #include "EEPARAMS.h"
442 #include "PARAMS.h"
443 C input parameter
444 _RL x
445 c local variable
446 _RL sf, rsf
447
448 if ( smoothAbsFuncRange .lt. 0.0 ) then
449 c limit of smoothMin(a,b) = .5*(a+b)
450 smoothAbs_R8 = 0.
451 else
452 if ( smoothAbsFuncRange .ne. 0.0 ) then
453 sf = 10.0D0/smoothAbsFuncRange
454 rsf = 1.D0/sf
455 else
456 c limit of smoothMin(a,b) = min(a,b)
457 sf = 0.D0
458 rsf = 0.D0
459 end if
460 c
461 if ( x .ge. smoothAbsFuncRange ) then
462 smoothAbs_R8 = x
463 else if ( x .le. -smoothAbsFuncRange ) then
464 smoothAbs_R8 = -x
465 else
466 smoothAbs_R8 = log(.5*(exp(x*sf)+exp(-x*sf)))*rsf
467 end if
468 end if
469
470 return
471 end
472 #endif /* USE_SMOOTH_MIN */
473
474 Cml#ifdef ALLOW_DEPTH_CONTROL
475 Cmlcadj SUBROUTINE limit_hfacc_to_one INPUT = 1
476 Cmlcadj SUBROUTINE limit_hfacc_to_one OUTPUT = 1
477 Cmlcadj SUBROUTINE limit_hfacc_to_one ACTIVE = 1
478 Cmlcadj SUBROUTINE limit_hfacc_to_one DEPEND = 1
479 Cmlcadj SUBROUTINE limit_hfacc_to_one REQUIRED
480 Cmlcadj SUBROUTINE limit_hfacc_to_one ADNAME = adlimit_hfacc_to_one
481 Cml#endif /* ALLOW_DEPTH_CONTROL */
482 Cml subroutine limit_hfacc_to_one( hf )
483 Cml
484 Cml _RL hf
485 Cml
486 Cml if ( hf .gt. 1. _d 0 ) then
487 Cml hf = 1. _d 0
488 Cml endif
489 Cml
490 Cml return
491 Cml end
492 Cml
493 Cml subroutine adlimit_hfacc_to_one( hf, adhf )
494 Cml
495 Cml _RL hf, adhf
496 Cml
497 Cml return
498 Cml end
499
500 #ifdef ALLOW_DEPTH_CONTROL
501 cadj SUBROUTINE dummy_in_hfac INPUT = 1, 2, 3
502 cadj SUBROUTINE dummy_in_hfac OUTPUT =
503 cadj SUBROUTINE dummy_in_hfac ACTIVE =
504 cadj SUBROUTINE dummy_in_hfac DEPEND = 1, 2, 3
505 cadj SUBROUTINE dummy_in_hfac REQUIRED
506 cadj SUBROUTINE dummy_in_hfac INFLUENCED
507 cadj SUBROUTINE dummy_in_hfac ADNAME = addummy_in_hfac
508 cadj SUBROUTINE dummy_in_hfac FTLNAME = g_dummy_in_hfac
509 #endif /* ALLOW_DEPTH_CONTROL */
510

  ViewVC Help
Powered by ViewVC 1.1.22