/[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.11 - (show annotations) (download)
Tue Apr 4 23:22:38 2017 UTC (7 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.10: +3 -3 lines
- add specific run-time param to select level of printed plot-field-maps,
  set by default to debugLevel.

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

  ViewVC Help
Powered by ViewVC 1.1.22