add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / Enum.lhs
1 \begin{code}
2 {-# LANGUAGE NoImplicitPrelude, BangPatterns, MagicHash #-}
3 {-# OPTIONS_HADDOCK hide #-}
4 -----------------------------------------------------------------------------
5 -- |
6 -- Module      :  GHC.Enum
7 -- Copyright   :  (c) The University of Glasgow, 1992-2002
8 -- License     :  see libraries/base/LICENSE
9 -- 
10 -- Maintainer  :  cvs-ghc@haskell.org
11 -- Stability   :  internal
12 -- Portability :  non-portable (GHC extensions)
13 --
14 -- The 'Enum' and 'Bounded' classes.
15 -- 
16 -----------------------------------------------------------------------------
17
18 -- #hide
19 module GHC.Enum(
20         Bounded(..), Enum(..),
21         boundedEnumFrom, boundedEnumFromThen,
22
23         -- Instances for Bounded and Enum: (), Char, Int
24
25    ) where
26
27 import GHC.Base
28 import Data.Tuple       ()              -- for dependencies
29 default ()              -- Double isn't available yet
30 \end{code}
31
32
33 %*********************************************************
34 %*                                                      *
35 \subsection{Class declarations}
36 %*                                                      *
37 %*********************************************************
38
39 \begin{code}
40 -- | The 'Bounded' class is used to name the upper and lower limits of a
41 -- type.  'Ord' is not a superclass of 'Bounded' since types that are not
42 -- totally ordered may also have upper and lower bounds.
43 --
44 -- The 'Bounded' class may be derived for any enumeration type;
45 -- 'minBound' is the first constructor listed in the @data@ declaration
46 -- and 'maxBound' is the last.
47 -- 'Bounded' may also be derived for single-constructor datatypes whose
48 -- constituent types are in 'Bounded'.
49
50 class  Bounded a  where
51     minBound, maxBound :: a
52
53 -- | Class 'Enum' defines operations on sequentially ordered types.
54 --
55 -- The @enumFrom@... methods are used in Haskell's translation of
56 -- arithmetic sequences.
57 --
58 -- Instances of 'Enum' may be derived for any enumeration type (types
59 -- whose constructors have no fields).  The nullary constructors are
60 -- assumed to be numbered left-to-right by 'fromEnum' from @0@ through @n-1@.
61 -- See Chapter 10 of the /Haskell Report/ for more details.
62 --  
63 -- For any type that is an instance of class 'Bounded' as well as 'Enum',
64 -- the following should hold:
65 --
66 -- * The calls @'succ' 'maxBound'@ and @'pred' 'minBound'@ should result in
67 --   a runtime error.
68 -- 
69 -- * 'fromEnum' and 'toEnum' should give a runtime error if the 
70 --   result value is not representable in the result type.
71 --   For example, @'toEnum' 7 :: 'Bool'@ is an error.
72 --
73 -- * 'enumFrom' and 'enumFromThen' should be defined with an implicit bound,
74 --   thus:
75 --
76 -- >    enumFrom     x   = enumFromTo     x maxBound
77 -- >    enumFromThen x y = enumFromThenTo x y bound
78 -- >      where
79 -- >        bound | fromEnum y >= fromEnum x = maxBound
80 -- >              | otherwise                = minBound
81 --
82 class  Enum a   where
83     -- | the successor of a value.  For numeric types, 'succ' adds 1.
84     succ                :: a -> a
85     -- | the predecessor of a value.  For numeric types, 'pred' subtracts 1.
86     pred                :: a -> a
87     -- | Convert from an 'Int'.
88     toEnum              :: Int -> a
89     -- | Convert to an 'Int'.
90     -- It is implementation-dependent what 'fromEnum' returns when
91     -- applied to a value that is too large to fit in an 'Int'.
92     fromEnum            :: a -> Int
93
94     -- | Used in Haskell's translation of @[n..]@.
95     enumFrom            :: a -> [a]
96     -- | Used in Haskell's translation of @[n,n'..]@.
97     enumFromThen        :: a -> a -> [a]
98     -- | Used in Haskell's translation of @[n..m]@.
99     enumFromTo          :: a -> a -> [a]
100     -- | Used in Haskell's translation of @[n,n'..m]@.
101     enumFromThenTo      :: a -> a -> a -> [a]
102
103     succ                   = toEnum . (`plusInt` oneInt)  . fromEnum
104     pred                   = toEnum . (`minusInt` oneInt) . fromEnum
105     enumFrom x             = map toEnum [fromEnum x ..]
106     enumFromThen x y       = map toEnum [fromEnum x, fromEnum y ..]
107     enumFromTo x y         = map toEnum [fromEnum x .. fromEnum y]
108     enumFromThenTo x1 x2 y = map toEnum [fromEnum x1, fromEnum x2 .. fromEnum y]
109
110 -- Default methods for bounded enumerations
111 boundedEnumFrom :: (Enum a, Bounded a) => a -> [a]
112 boundedEnumFrom n = map toEnum [fromEnum n .. fromEnum (maxBound `asTypeOf` n)]
113
114 boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a]
115 boundedEnumFromThen n1 n2 
116   | i_n2 >= i_n1  = map toEnum [i_n1, i_n2 .. fromEnum (maxBound `asTypeOf` n1)]
117   | otherwise     = map toEnum [i_n1, i_n2 .. fromEnum (minBound `asTypeOf` n1)]
118   where
119     i_n1 = fromEnum n1
120     i_n2 = fromEnum n2
121 \end{code}
122
123
124 %*********************************************************
125 %*                                                      *
126 \subsection{Tuples}
127 %*                                                      *
128 %*********************************************************
129
130 \begin{code}
131 instance Bounded () where
132     minBound = ()
133     maxBound = ()
134
135 instance Enum () where
136     succ _      = error "Prelude.Enum.().succ: bad argument"
137     pred _      = error "Prelude.Enum.().pred: bad argument"
138
139     toEnum x | x == zeroInt = ()
140              | otherwise    = error "Prelude.Enum.().toEnum: bad argument"
141
142     fromEnum () = zeroInt
143     enumFrom ()         = [()]
144     enumFromThen () ()  = let many = ():many in many
145     enumFromTo () ()    = [()]
146     enumFromThenTo () () () = let many = ():many in many
147 \end{code}
148
149 \begin{code}
150 -- Report requires instances up to 15
151 instance (Bounded a, Bounded b) => Bounded (a,b) where
152    minBound = (minBound, minBound)
153    maxBound = (maxBound, maxBound)
154
155 instance (Bounded a, Bounded b, Bounded c) => Bounded (a,b,c) where
156    minBound = (minBound, minBound, minBound)
157    maxBound = (maxBound, maxBound, maxBound)
158
159 instance (Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a,b,c,d) where
160    minBound = (minBound, minBound, minBound, minBound)
161    maxBound = (maxBound, maxBound, maxBound, maxBound)
162
163 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a,b,c,d,e) where
164    minBound = (minBound, minBound, minBound, minBound, minBound)
165    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound)
166
167 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f)
168         => Bounded (a,b,c,d,e,f) where
169    minBound = (minBound, minBound, minBound, minBound, minBound, minBound)
170    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound)
171
172 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g)
173         => Bounded (a,b,c,d,e,f,g) where
174    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound)
175    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound)
176
177 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
178           Bounded h)
179         => Bounded (a,b,c,d,e,f,g,h) where
180    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound)
181    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound)
182
183 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
184           Bounded h, Bounded i)
185         => Bounded (a,b,c,d,e,f,g,h,i) where
186    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound,
187                minBound)
188    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound,
189                maxBound)
190
191 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
192           Bounded h, Bounded i, Bounded j)
193         => Bounded (a,b,c,d,e,f,g,h,i,j) where
194    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound,
195                minBound, minBound)
196    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound,
197                maxBound, maxBound)
198
199 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
200           Bounded h, Bounded i, Bounded j, Bounded k)
201         => Bounded (a,b,c,d,e,f,g,h,i,j,k) where
202    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound,
203                minBound, minBound, minBound)
204    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound,
205                maxBound, maxBound, maxBound)
206
207 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
208           Bounded h, Bounded i, Bounded j, Bounded k, Bounded l)
209         => Bounded (a,b,c,d,e,f,g,h,i,j,k,l) where
210    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound,
211                minBound, minBound, minBound, minBound)
212    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound,
213                maxBound, maxBound, maxBound, maxBound)
214
215 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
216           Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m)
217         => Bounded (a,b,c,d,e,f,g,h,i,j,k,l,m) where
218    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound,
219                minBound, minBound, minBound, minBound, minBound)
220    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound,
221                maxBound, maxBound, maxBound, maxBound, maxBound)
222
223 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
224           Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n)
225         => Bounded (a,b,c,d,e,f,g,h,i,j,k,l,m,n) where
226    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound,
227                minBound, minBound, minBound, minBound, minBound, minBound)
228    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound,
229                maxBound, maxBound, maxBound, maxBound, maxBound, maxBound)
230
231 instance (Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g,
232           Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o)
233         => Bounded (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) where
234    minBound = (minBound, minBound, minBound, minBound, minBound, minBound, minBound, minBound,
235                minBound, minBound, minBound, minBound, minBound, minBound, minBound)
236    maxBound = (maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound,
237                maxBound, maxBound, maxBound, maxBound, maxBound, maxBound, maxBound)
238 \end{code}
239
240
241 %*********************************************************
242 %*                                                      *
243 \subsection{Type @Bool@}
244 %*                                                      *
245 %*********************************************************
246
247 \begin{code}
248 instance Bounded Bool where
249   minBound = False
250   maxBound = True
251
252 instance Enum Bool where
253   succ False = True
254   succ True  = error "Prelude.Enum.Bool.succ: bad argument"
255
256   pred True  = False
257   pred False  = error "Prelude.Enum.Bool.pred: bad argument"
258
259   toEnum n | n == zeroInt = False
260            | n == oneInt  = True
261            | otherwise    = error "Prelude.Enum.Bool.toEnum: bad argument"
262
263   fromEnum False = zeroInt
264   fromEnum True  = oneInt
265
266   -- Use defaults for the rest
267   enumFrom     = boundedEnumFrom
268   enumFromThen = boundedEnumFromThen
269 \end{code}
270
271 %*********************************************************
272 %*                                                      *
273 \subsection{Type @Ordering@}
274 %*                                                      *
275 %*********************************************************
276
277 \begin{code}
278 instance Bounded Ordering where
279   minBound = LT
280   maxBound = GT
281
282 instance Enum Ordering where
283   succ LT = EQ
284   succ EQ = GT
285   succ GT = error "Prelude.Enum.Ordering.succ: bad argument"
286
287   pred GT = EQ
288   pred EQ = LT
289   pred LT = error "Prelude.Enum.Ordering.pred: bad argument"
290
291   toEnum n | n == zeroInt = LT
292            | n == oneInt  = EQ
293            | n == twoInt  = GT
294   toEnum _ = error "Prelude.Enum.Ordering.toEnum: bad argument"
295
296   fromEnum LT = zeroInt
297   fromEnum EQ = oneInt
298   fromEnum GT = twoInt
299
300   -- Use defaults for the rest
301   enumFrom     = boundedEnumFrom
302   enumFromThen = boundedEnumFromThen
303 \end{code}
304
305 %*********************************************************
306 %*                                                      *
307 \subsection{Type @Char@}
308 %*                                                      *
309 %*********************************************************
310
311 \begin{code}
312 instance  Bounded Char  where
313     minBound =  '\0'
314     maxBound =  '\x10FFFF'
315
316 instance  Enum Char  where
317     succ (C# c#)
318        | not (ord# c# ==# 0x10FFFF#) = C# (chr# (ord# c# +# 1#))
319        | otherwise              = error ("Prelude.Enum.Char.succ: bad argument")
320     pred (C# c#)
321        | not (ord# c# ==# 0#)   = C# (chr# (ord# c# -# 1#))
322        | otherwise              = error ("Prelude.Enum.Char.pred: bad argument")
323
324     toEnum   = chr
325     fromEnum = ord
326
327     {-# INLINE enumFrom #-}
328     enumFrom (C# x) = eftChar (ord# x) 0x10FFFF#
329         -- Blarg: technically I guess enumFrom isn't strict!
330
331     {-# INLINE enumFromTo #-}
332     enumFromTo (C# x) (C# y) = eftChar (ord# x) (ord# y)
333     
334     {-# INLINE enumFromThen #-}
335     enumFromThen (C# x1) (C# x2) = efdChar (ord# x1) (ord# x2)
336     
337     {-# INLINE enumFromThenTo #-}
338     enumFromThenTo (C# x1) (C# x2) (C# y) = efdtChar (ord# x1) (ord# x2) (ord# y)
339
340 {-# RULES
341 "eftChar"       [~1] forall x y.        eftChar x y       = build (\c n -> eftCharFB c n x y)
342 "efdChar"       [~1] forall x1 x2.      efdChar x1 x2     = build (\ c n -> efdCharFB c n x1 x2)
343 "efdtChar"      [~1] forall x1 x2 l.    efdtChar x1 x2 l  = build (\ c n -> efdtCharFB c n x1 x2 l)
344 "eftCharList"   [1]  eftCharFB  (:) [] = eftChar
345 "efdCharList"   [1]  efdCharFB  (:) [] = efdChar
346 "efdtCharList"  [1]  efdtCharFB (:) [] = efdtChar
347  #-}
348
349
350 -- We can do better than for Ints because we don't
351 -- have hassles about arithmetic overflow at maxBound
352 {-# INLINE [0] eftCharFB #-}
353 eftCharFB :: (Char -> a -> a) -> a -> Int# -> Int# -> a
354 eftCharFB c n x0 y = go x0
355                  where
356                     go x | x ># y    = n
357                          | otherwise = C# (chr# x) `c` go (x +# 1#)
358
359 eftChar :: Int# -> Int# -> String
360 eftChar x y | x ># y    = []
361             | otherwise = C# (chr# x) : eftChar (x +# 1#) y
362
363
364 -- For enumFromThenTo we give up on inlining
365 {-# NOINLINE [0] efdCharFB #-}
366 efdCharFB :: (Char -> a -> a) -> a -> Int# -> Int# -> a
367 efdCharFB c n x1 x2
368   | delta >=# 0# = go_up_char_fb c n x1 delta 0x10FFFF#
369   | otherwise    = go_dn_char_fb c n x1 delta 0#
370   where
371     !delta = x2 -# x1
372
373 efdChar :: Int# -> Int# -> String
374 efdChar x1 x2
375   | delta >=# 0# = go_up_char_list x1 delta 0x10FFFF#
376   | otherwise    = go_dn_char_list x1 delta 0#
377   where
378     !delta = x2 -# x1
379
380 {-# NOINLINE [0] efdtCharFB #-}
381 efdtCharFB :: (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> a
382 efdtCharFB c n x1 x2 lim
383   | delta >=# 0# = go_up_char_fb c n x1 delta lim
384   | otherwise    = go_dn_char_fb c n x1 delta lim
385   where
386     !delta = x2 -# x1
387
388 efdtChar :: Int# -> Int# -> Int# -> String
389 efdtChar x1 x2 lim
390   | delta >=# 0# = go_up_char_list x1 delta lim
391   | otherwise    = go_dn_char_list x1 delta lim
392   where
393     !delta = x2 -# x1
394
395 go_up_char_fb :: (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> a
396 go_up_char_fb c n x0 delta lim
397   = go_up x0
398   where
399     go_up x | x ># lim  = n
400             | otherwise = C# (chr# x) `c` go_up (x +# delta)
401
402 go_dn_char_fb :: (Char -> a -> a) -> a -> Int# -> Int# -> Int# -> a
403 go_dn_char_fb c n x0 delta lim
404   = go_dn x0
405   where
406     go_dn x | x <# lim  = n
407             | otherwise = C# (chr# x) `c` go_dn (x +# delta)
408
409 go_up_char_list :: Int# -> Int# -> Int# -> String
410 go_up_char_list x0 delta lim
411   = go_up x0
412   where
413     go_up x | x ># lim  = []
414             | otherwise = C# (chr# x) : go_up (x +# delta)
415
416 go_dn_char_list :: Int# -> Int# -> Int# -> String
417 go_dn_char_list x0 delta lim
418   = go_dn x0
419   where
420     go_dn x | x <# lim  = []
421             | otherwise = C# (chr# x) : go_dn (x +# delta)
422 \end{code}
423
424
425 %*********************************************************
426 %*                                                      *
427 \subsection{Type @Int@}
428 %*                                                      *
429 %*********************************************************
430
431 Be careful about these instances.  
432         (a) remember that you have to count down as well as up e.g. [13,12..0]
433         (b) be careful of Int overflow
434         (c) remember that Int is bounded, so [1..] terminates at maxInt
435
436 Also NB that the Num class isn't available in this module.
437         
438 \begin{code}
439 instance  Bounded Int where
440     minBound =  minInt
441     maxBound =  maxInt
442
443 instance  Enum Int  where
444     succ x  
445        | x == maxBound  = error "Prelude.Enum.succ{Int}: tried to take `succ' of maxBound"
446        | otherwise      = x `plusInt` oneInt
447     pred x
448        | x == minBound  = error "Prelude.Enum.pred{Int}: tried to take `pred' of minBound"
449        | otherwise      = x `minusInt` oneInt
450
451     toEnum   x = x
452     fromEnum x = x
453
454     {-# INLINE enumFrom #-}
455     enumFrom (I# x) = eftInt x maxInt#
456         where !(I# maxInt#) = maxInt
457         -- Blarg: technically I guess enumFrom isn't strict!
458
459     {-# INLINE enumFromTo #-}
460     enumFromTo (I# x) (I# y) = eftInt x y
461
462     {-# INLINE enumFromThen #-}
463     enumFromThen (I# x1) (I# x2) = efdInt x1 x2
464
465     {-# INLINE enumFromThenTo #-}
466     enumFromThenTo (I# x1) (I# x2) (I# y) = efdtInt x1 x2 y
467
468
469 -----------------------------------------------------
470 -- eftInt and eftIntFB deal with [a..b], which is the 
471 -- most common form, so we take a lot of care
472 -- In particular, we have rules for deforestation
473
474 {-# RULES
475 "eftInt"        [~1] forall x y. eftInt x y = build (\ c n -> eftIntFB c n x y)
476 "eftIntList"    [1] eftIntFB  (:) [] = eftInt
477  #-}
478
479 eftInt :: Int# -> Int# -> [Int]
480 -- [x1..x2]
481 eftInt x0 y | x0 ># y    = []
482             | otherwise = go x0
483                where
484                  go x = I# x : if x ==# y then [] else go (x +# 1#)
485
486 {-# INLINE [0] eftIntFB #-}
487 eftIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> r
488 eftIntFB c n x0 y | x0 ># y    = n        
489                   | otherwise = go x0
490                  where
491                    go x = I# x `c` if x ==# y then n else go (x +# 1#)
492                         -- Watch out for y=maxBound; hence ==, not >
493         -- Be very careful not to have more than one "c"
494         -- so that when eftInfFB is inlined we can inline
495         -- whatever is bound to "c"
496
497
498 -----------------------------------------------------
499 -- efdInt and efdtInt deal with [a,b..] and [a,b..c].
500 -- The code is more complicated because of worries about Int overflow.
501
502 {-# RULES
503 "efdtInt"       [~1] forall x1 x2 y.
504                      efdtInt x1 x2 y = build (\ c n -> efdtIntFB c n x1 x2 y)
505 "efdtIntUpList" [1]  efdtIntFB (:) [] = efdtInt
506  #-}
507
508 efdInt :: Int# -> Int# -> [Int]
509 -- [x1,x2..maxInt]
510 efdInt x1 x2 
511  | x2 >=# x1 = case maxInt of I# y -> efdtIntUp x1 x2 y
512  | otherwise = case minInt of I# y -> efdtIntDn x1 x2 y
513
514 efdtInt :: Int# -> Int# -> Int# -> [Int]
515 -- [x1,x2..y]
516 efdtInt x1 x2 y
517  | x2 >=# x1 = efdtIntUp x1 x2 y
518  | otherwise = efdtIntDn x1 x2 y
519
520 {-# INLINE [0] efdtIntFB #-}
521 efdtIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> r
522 efdtIntFB c n x1 x2 y
523  | x2 >=# x1  = efdtIntUpFB c n x1 x2 y
524  | otherwise  = efdtIntDnFB c n x1 x2 y
525
526 -- Requires x2 >= x1
527 efdtIntUp :: Int# -> Int# -> Int# -> [Int]
528 efdtIntUp x1 x2 y    -- Be careful about overflow!
529  | y <# x2   = if y <# x1 then [] else [I# x1]
530  | otherwise = -- Common case: x1 <= x2 <= y
531                let !delta = x2 -# x1 -- >= 0
532                    !y' = y -# delta  -- x1 <= y' <= y; hence y' is representable
533
534                    -- Invariant: x <= y
535                    -- Note that: z <= y' => z + delta won't overflow
536                    -- so we are guaranteed not to overflow if/when we recurse
537                    go_up x | x ># y'  = [I# x]
538                            | otherwise = I# x : go_up (x +# delta)
539                in I# x1 : go_up x2
540
541 -- Requires x2 >= x1
542 efdtIntUpFB :: (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> r
543 efdtIntUpFB c n x1 x2 y    -- Be careful about overflow!
544  | y <# x2   = if y <# x1 then n else I# x1 `c` n
545  | otherwise = -- Common case: x1 <= x2 <= y
546                let !delta = x2 -# x1 -- >= 0
547                    !y' = y -# delta  -- x1 <= y' <= y; hence y' is representable
548
549                    -- Invariant: x <= y
550                    -- Note that: z <= y' => z + delta won't overflow
551                    -- so we are guaranteed not to overflow if/when we recurse
552                    go_up x | x ># y'   = I# x `c` n
553                            | otherwise = I# x `c` go_up (x +# delta)
554                in I# x1 `c` go_up x2
555
556 -- Requires x2 <= x1
557 efdtIntDn :: Int# -> Int# -> Int# -> [Int]
558 efdtIntDn x1 x2 y    -- Be careful about underflow!
559  | y ># x2   = if y ># x1 then [] else [I# x1]
560  | otherwise = -- Common case: x1 >= x2 >= y
561                let !delta = x2 -# x1 -- <= 0
562                    !y' = y -# delta  -- y <= y' <= x1; hence y' is representable
563
564                    -- Invariant: x >= y
565                    -- Note that: z >= y' => z + delta won't underflow
566                    -- so we are guaranteed not to underflow if/when we recurse
567                    go_dn x | x <# y'  = [I# x]
568                            | otherwise = I# x : go_dn (x +# delta)
569    in I# x1 : go_dn x2
570
571 -- Requires x2 <= x1
572 efdtIntDnFB :: (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> r
573 efdtIntDnFB c n x1 x2 y    -- Be careful about underflow!
574  | y ># x2 = if y ># x1 then n else I# x1 `c` n
575  | otherwise = -- Common case: x1 >= x2 >= y
576                let !delta = x2 -# x1 -- <= 0
577                    !y' = y -# delta  -- y <= y' <= x1; hence y' is representable
578
579                    -- Invariant: x >= y
580                    -- Note that: z >= y' => z + delta won't underflow
581                    -- so we are guaranteed not to underflow if/when we recurse
582                    go_dn x | x <# y'   = I# x `c` n
583                            | otherwise = I# x `c` go_dn (x +# delta)
584                in I# x1 `c` go_dn x2
585 \end{code}
586