/[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.9 - (show annotations) (download)
Sun Aug 12 20:24:23 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63r, checkpoint63s, checkpoint64
Changes since 1.8: +2 -1 lines
add PACKAGES_CONFIG.h wherever ALLOW_AUTODIFF[_TAMC] is used (in model/src)

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

  ViewVC Help
Powered by ViewVC 1.1.22