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