/[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.8 - (hide annotations) (download)
Sun Jun 17 14:17:26 2012 UTC (11 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63o
Changes since 1.7: +125 -140 lines
- rename SMOOTH*_R4,R8 function to the corresponding type (_RS & _RL)
- remove (re-)setting of kSurfW & kSurfS ;
- save hFac[CWS] into h0Fac[CWS] ;
- few editing (e.g., list the Content of this file).

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

  ViewVC Help
Powered by ViewVC 1.1.22