89c8b67341861c4e2d88cf50d858edf73d84f2e4
[ghc-base.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 {-# SOURCE #-} GHC.Err ( error )
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 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 \end{code}
162
163
164 %*********************************************************
165 %*                                                      *
166 \subsection{Type @Bool@}
167 %*                                                      *
168 %*********************************************************
169
170 \begin{code}
171 instance Bounded Bool where
172   minBound = False
173   maxBound = True
174
175 instance Enum Bool where
176   succ False = True
177   succ True  = error "Prelude.Enum.Bool.succ: bad argument"
178
179   pred True  = False
180   pred False  = error "Prelude.Enum.Bool.pred: bad argument"
181
182   toEnum n | n == zeroInt = False
183            | n == oneInt  = True
184            | otherwise    = error "Prelude.Enum.Bool.toEnum: bad argument"
185
186   fromEnum False = zeroInt
187   fromEnum True  = oneInt
188
189   -- Use defaults for the rest
190   enumFrom     = boundedEnumFrom
191   enumFromThen = boundedEnumFromThen
192 \end{code}
193
194 %*********************************************************
195 %*                                                      *
196 \subsection{Type @Ordering@}
197 %*                                                      *
198 %*********************************************************
199
200 \begin{code}
201 instance Bounded Ordering where
202   minBound = LT
203   maxBound = GT
204
205 instance Enum Ordering where
206   succ LT = EQ
207   succ EQ = GT
208   succ GT = error "Prelude.Enum.Ordering.succ: bad argument"
209
210   pred GT = EQ
211   pred EQ = LT
212   pred LT = error "Prelude.Enum.Ordering.pred: bad argument"
213
214   toEnum n | n == zeroInt = LT
215            | n == oneInt  = EQ
216            | n == twoInt  = GT
217   toEnum _ = error "Prelude.Enum.Ordering.toEnum: bad argument"
218
219   fromEnum LT = zeroInt
220   fromEnum EQ = oneInt
221   fromEnum GT = twoInt
222
223   -- Use defaults for the rest
224   enumFrom     = boundedEnumFrom
225   enumFromThen = boundedEnumFromThen
226 \end{code}
227
228 %*********************************************************
229 %*                                                      *
230 \subsection{Type @Char@}
231 %*                                                      *
232 %*********************************************************
233
234 \begin{code}
235 instance  Bounded Char  where
236     minBound =  '\0'
237     maxBound =  '\x10FFFF'
238
239 instance  Enum Char  where
240     succ (C# c#)
241        | not (ord# c# ==# 0x10FFFF#) = C# (chr# (ord# c# +# 1#))
242        | otherwise              = error ("Prelude.Enum.Char.succ: bad argument")
243     pred (C# c#)
244        | not (ord# c# ==# 0#)   = C# (chr# (ord# c# -# 1#))
245        | otherwise              = error ("Prelude.Enum.Char.pred: bad argument")
246
247     toEnum   = chr
248     fromEnum = ord
249
250     {-# INLINE enumFrom #-}
251     enumFrom (C# x) = eftChar (ord# x) 0x10FFFF#
252         -- Blarg: technically I guess enumFrom isn't strict!
253
254     {-# INLINE enumFromTo #-}
255     enumFromTo (C# x) (C# y) = eftChar (ord# x) (ord# y)
256     
257     {-# INLINE enumFromThen #-}
258     enumFromThen (C# x1) (C# x2) = efdChar (ord# x1) (ord# x2)
259     
260     {-# INLINE enumFromThenTo #-}
261     enumFromThenTo (C# x1) (C# x2) (C# y) = efdtChar (ord# x1) (ord# x2) (ord# y)
262
263 {-# RULES
264 "eftChar"       [~1] forall x y.        eftChar x y       = build (\c n -> eftCharFB c n x y)
265 "efdChar"       [~1] forall x1 x2.      efdChar x1 x2     = build (\ c n -> efdCharFB c n x1 x2)
266 "efdtChar"      [~1] forall x1 x2 l.    efdtChar x1 x2 l  = build (\ c n -> efdtCharFB c n x1 x2 l)
267 "eftCharList"   [1]  eftCharFB  (:) [] = eftChar
268 "efdCharList"   [1]  efdCharFB  (:) [] = efdChar
269 "efdtCharList"  [1]  efdtCharFB (:) [] = efdtChar
270  #-}
271
272
273 -- We can do better than for Ints because we don't
274 -- have hassles about arithmetic overflow at maxBound
275 {-# INLINE [0] eftCharFB #-}
276 eftCharFB c n x y = go x
277                  where
278                     go x | x ># y    = n
279                          | otherwise = C# (chr# x) `c` go (x +# 1#)
280
281 eftChar x y | x ># y    = [] 
282                 | otherwise = C# (chr# x) : eftChar (x +# 1#) y
283
284
285 -- For enumFromThenTo we give up on inlining
286 {-# NOINLINE [0] efdCharFB #-}
287 efdCharFB c n x1 x2
288   | delta >=# 0# = go_up_char_fb c n x1 delta 0x10FFFF#
289   | otherwise    = go_dn_char_fb c n x1 delta 0#
290   where
291     delta = x2 -# x1
292
293 efdChar x1 x2
294   | delta >=# 0# = go_up_char_list x1 delta 0x10FFFF#
295   | otherwise    = go_dn_char_list x1 delta 0#
296   where
297     delta = x2 -# x1
298
299 {-# NOINLINE [0] efdtCharFB #-}
300 efdtCharFB c n x1 x2 lim
301   | delta >=# 0# = go_up_char_fb c n x1 delta lim
302   | otherwise    = go_dn_char_fb c n x1 delta lim
303   where
304     delta = x2 -# x1
305
306 efdtChar x1 x2 lim
307   | delta >=# 0# = go_up_char_list x1 delta lim
308   | otherwise    = go_dn_char_list x1 delta lim
309   where
310     delta = x2 -# x1
311
312 go_up_char_fb c n x delta lim
313   = go_up x
314   where
315     go_up x | x ># lim  = n
316             | otherwise = C# (chr# x) `c` go_up (x +# delta)
317
318 go_dn_char_fb c n x delta lim
319   = go_dn x
320   where
321     go_dn x | x <# lim  = n
322             | otherwise = C# (chr# x) `c` go_dn (x +# delta)
323
324 go_up_char_list x delta lim
325   = go_up x
326   where
327     go_up x | x ># lim  = []
328             | otherwise = C# (chr# x) : go_up (x +# delta)
329
330 go_dn_char_list x delta lim
331   = go_dn x
332   where
333     go_dn x | x <# lim  = []
334             | otherwise = C# (chr# x) : go_dn (x +# delta)
335 \end{code}
336
337
338 %*********************************************************
339 %*                                                      *
340 \subsection{Type @Int@}
341 %*                                                      *
342 %*********************************************************
343
344 Be careful about these instances.  
345         (a) remember that you have to count down as well as up e.g. [13,12..0]
346         (b) be careful of Int overflow
347         (c) remember that Int is bounded, so [1..] terminates at maxInt
348
349 Also NB that the Num class isn't available in this module.
350         
351 \begin{code}
352 instance  Bounded Int where
353     minBound =  minInt
354     maxBound =  maxInt
355
356 instance  Enum Int  where
357     succ x  
358        | x == maxBound  = error "Prelude.Enum.succ{Int}: tried to take `succ' of maxBound"
359        | otherwise      = x `plusInt` oneInt
360     pred x
361        | x == minBound  = error "Prelude.Enum.pred{Int}: tried to take `pred' of minBound"
362        | otherwise      = x `minusInt` oneInt
363
364     toEnum   x = x
365     fromEnum x = x
366
367     {-# INLINE enumFrom #-}
368     enumFrom (I# x) = eftInt x maxInt#
369         where I# maxInt# = maxInt
370         -- Blarg: technically I guess enumFrom isn't strict!
371
372     {-# INLINE enumFromTo #-}
373     enumFromTo (I# x) (I# y) = eftInt x y
374
375     {-# INLINE enumFromThen #-}
376     enumFromThen (I# x1) (I# x2) = efdInt x1 x2
377
378     {-# INLINE enumFromThenTo #-}
379     enumFromThenTo (I# x1) (I# x2) (I# y) = efdtInt x1 x2 y
380
381
382 -----------------------------------------------------
383 -- eftInt and eftIntFB deal with [a..b], which is the 
384 -- most common form, so we take a lot of care
385 -- In particular, we have rules for deforestation
386
387 {-# RULES
388 "eftInt"        [~1] forall x y. eftInt x y = build (\ c n -> eftIntFB c n x y)
389 "eftIntList"    [1] eftIntFB  (:) [] = eftInt
390  #-}
391
392 eftInt :: Int# -> Int# -> [Int]
393 -- [x1..x2]
394 eftInt x y | x ># y    = []
395            | otherwise = go x
396                where
397                  go x = I# x : if x ==# y then [] else go (x +# 1#)
398
399 {-# INLINE [0] eftIntFB #-}
400 eftIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> r
401 eftIntFB c n x y | x ># y    = n        
402                  | otherwise = go x
403                  where
404                    go x = I# x `c` if x ==# y then n else go (x +# 1#)
405                         -- Watch out for y=maxBound; hence ==, not >
406         -- Be very careful not to have more than one "c"
407         -- so that when eftInfFB is inlined we can inline
408         -- whatver is bound to "c"
409
410
411 -----------------------------------------------------
412 -- efdInt and efdtInt deal with [a,b..] and [a,b..c], which are much less common
413 -- so we are less elaborate.  The code is more complicated anyway, because
414 -- of worries about Int overflow, so we don't both with rules and deforestation
415
416 efdInt :: Int# -> Int# -> [Int]
417 -- [x1,x2..maxInt]
418 efdInt x1 x2 
419   | x2 >=# x1 = case maxInt of I# y -> efdtIntUp x1 x2 y
420   | otherwise = case minInt of I# y -> efdtIntDn x1 x2 y
421
422 efdtInt :: Int# -> Int# -> Int# -> [Int]
423 -- [x1,x2..y]
424 efdtInt x1 x2 y
425   | x2 >=# x1  = efdtIntUp x1 x2 y
426   | otherwise  = efdtIntDn x1 x2 y
427
428 efdtIntUp :: Int# -> Int# -> Int# -> [Int]
429 efdtIntUp x1 x2 y       -- Be careful about overflow!
430   | y <# x2    = if y <# x1 then [] else [I# x1]
431   | otherwise 
432   =     -- Common case: x1 < x2 <= y
433     let 
434         delta = x2 -# x1        
435         y' = y -# delta 
436         -- NB: x1 <= y'; hence y' is representable
437
438         -- Invariant: x <= y; and x+delta won't overflow
439         go_up x | x ># y'  = [I# x]
440                 | otherwise = I# x : go_up (x +# delta)
441     in 
442     I# x1 : go_up x2
443                         
444 efdtIntDn :: Int# -> Int# -> Int# -> [Int]
445 efdtIntDn x1 x2 y       -- x2 < x1
446   | y ># x2    = if y ># x1 then [] else [I# x1]
447   | otherwise 
448   =     -- Common case: x1 > x2 >= y
449     let 
450         delta = x2 -# x1        
451         y' = y -# delta 
452         -- NB: x1 <= y'; hence y' is representable
453
454         -- Invariant: x >= y; and x+delta won't overflow
455         go_dn x | x <# y'  = [I# x]
456                 | otherwise = I# x : go_dn (x +# delta)
457     in 
458     I# x1 : go_dn x2
459 \end{code}
460