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

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

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


Revision 1.3 - (hide annotations) (download)
Tue Apr 28 18:01:15 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint61n, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.2: +9 -9 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable

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

  ViewVC Help
Powered by ViewVC 1.1.22