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