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