[project @ 2004-07-23 13:24:04 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); see Chapter 10 of the /Haskell Report/.
59 --  
60 -- For any type that is an instance of class 'Bounded' as well as 'Enum',
61 -- the following should hold:
62 --
63 -- * The calls @'succ' 'maxBound'@ and @'pred' 'minBound'@ should result in
64 --   a runtime error.
65 -- 
66 -- * 'fromEnum' and 'toEnum' should give a runtime error if the 
67 --   result value is not representable in the result type.
68 --   For example, @'toEnum' 7 :: 'Bool'@ is an error.
69 --
70 -- * 'enumFrom' and 'enumFromThen' should be defined with an implicit bound,
71 --   thus:
72 --
73 -- >    enumFrom     x   = enumFromTo     x maxBound
74 -- >    enumFromThen x y = enumFromThenTo x y bound
75 -- >      where
76 -- >        bound | fromEnum y >= fromEnum x = maxBound
77 -- >              | otherwise                = minBound
78 --
79 class  Enum a   where
80     -- | the successor of a value.  For numeric types, 'succ' adds 1.
81     succ                :: a -> a
82     -- | the predecessor of a value.  For numeric types, 'pred' subtracts 1.
83     pred                :: a -> a
84     -- | Convert from an 'Int'.
85     toEnum              :: Int -> a
86     -- | Convert to an 'Int'.
87     -- It is implementation-dependent what 'fromEnum' returns when
88     -- applied to a value that is too large to fit in an 'Int'.
89     fromEnum            :: a -> Int
90
91     -- | Used in Haskell's translation of @[n..]@.
92     enumFrom            :: a -> [a]
93     -- | Used in Haskell's translation of @[n,n'..]@.
94     enumFromThen        :: a -> a -> [a]
95     -- | Used in Haskell's translation of @[n..m]@.
96     enumFromTo          :: a -> a -> [a]
97     -- | Used in Haskell's translation of @[n,n'..m]@.
98     enumFromThenTo      :: a -> a -> a -> [a]
99
100     succ                   = toEnum . (`plusInt` oneInt)  . fromEnum
101     pred                   = toEnum . (`minusInt` oneInt) . fromEnum
102     enumFrom x             = map toEnum [fromEnum x ..]
103     enumFromThen x y       = map toEnum [fromEnum x, fromEnum y ..]
104     enumFromTo x y         = map toEnum [fromEnum x .. fromEnum y]
105     enumFromThenTo x1 x2 y = map toEnum [fromEnum x1, fromEnum x2 .. fromEnum y]
106
107 -- Default methods for bounded enumerations
108 boundedEnumFrom :: (Enum a, Bounded a) => a -> [a]
109 boundedEnumFrom n = map toEnum [fromEnum n .. fromEnum (maxBound `asTypeOf` n)]
110
111 boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a]
112 boundedEnumFromThen n1 n2 
113   | i_n2 >= i_n1  = map toEnum [i_n1, i_n2 .. fromEnum (maxBound `asTypeOf` n1)]
114   | otherwise     = map toEnum [i_n1, i_n2 .. fromEnum (minBound `asTypeOf` n1)]
115   where
116     i_n1 = fromEnum n1
117     i_n2 = fromEnum n2
118 \end{code}
119
120
121 %*********************************************************
122 %*                                                      *
123 \subsection{Tuples}
124 %*                                                      *
125 %*********************************************************
126
127 \begin{code}
128 instance Bounded () where
129     minBound = ()
130     maxBound = ()
131
132 instance Enum () where
133     succ _      = error "Prelude.Enum.().succ: bad argment"
134     pred _      = error "Prelude.Enum.().pred: bad argument"
135
136     toEnum x | x == zeroInt = ()
137              | otherwise    = error "Prelude.Enum.().toEnum: bad argument"
138
139     fromEnum () = zeroInt
140     enumFrom ()         = [()]
141     enumFromThen () ()  = [()]
142     enumFromTo () ()    = [()]
143     enumFromThenTo () () () = [()]
144 \end{code}
145
146 \begin{code}
147 instance (Bounded a, Bounded b) => Bounded (a,b) where
148    minBound = (minBound, minBound)
149    maxBound = (maxBound, maxBound)
150
151 instance (Bounded a, Bounded b, Bounded c) => Bounded (a,b,c) where
152    minBound = (minBound, minBound, minBound)
153    maxBound = (maxBound, maxBound, maxBound)
154
155 instance (Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a,b,c,d) where
156    minBound = (minBound, minBound, minBound, minBound)
157    maxBound = (maxBound, maxBound, maxBound, maxBound)
158 \end{code}
159
160
161 %*********************************************************
162 %*                                                      *
163 \subsection{Type @Bool@}
164 %*                                                      *
165 %*********************************************************
166
167 \begin{code}
168 instance Bounded Bool where
169   minBound = False
170   maxBound = True
171
172 instance Enum Bool where
173   succ False = True
174   succ True  = error "Prelude.Enum.Bool.succ: bad argment"
175
176   pred True  = False
177   pred False  = error "Prelude.Enum.Bool.pred: bad argment"
178
179   toEnum n | n == zeroInt = False
180            | n == oneInt  = True
181            | otherwise    = error "Prelude.Enum.Bool.toEnum: bad argment"
182
183   fromEnum False = zeroInt
184   fromEnum True  = oneInt
185
186   -- Use defaults for the rest
187   enumFrom     = boundedEnumFrom
188   enumFromThen = boundedEnumFromThen
189 \end{code}
190
191 %*********************************************************
192 %*                                                      *
193 \subsection{Type @Ordering@}
194 %*                                                      *
195 %*********************************************************
196
197 \begin{code}
198 instance Bounded Ordering where
199   minBound = LT
200   maxBound = GT
201
202 instance Enum Ordering where
203   succ LT = EQ
204   succ EQ = GT
205   succ GT = error "Prelude.Enum.Ordering.succ: bad argment"
206
207   pred GT = EQ
208   pred EQ = LT
209   pred LT = error "Prelude.Enum.Ordering.pred: bad argment"
210
211   toEnum n | n == zeroInt = LT
212            | n == oneInt  = EQ
213            | n == twoInt  = GT
214   toEnum _ = error "Prelude.Enum.Ordering.toEnum: bad argment"
215
216   fromEnum LT = zeroInt
217   fromEnum EQ = oneInt
218   fromEnum GT = twoInt
219
220   -- Use defaults for the rest
221   enumFrom     = boundedEnumFrom
222   enumFromThen = boundedEnumFromThen
223 \end{code}
224
225 %*********************************************************
226 %*                                                      *
227 \subsection{Type @Char@}
228 %*                                                      *
229 %*********************************************************
230
231 \begin{code}
232 instance  Bounded Char  where
233     minBound =  '\0'
234     maxBound =  '\x10FFFF'
235
236 instance  Enum Char  where
237     succ (C# c#)
238        | not (ord# c# ==# 0x10FFFF#) = C# (chr# (ord# c# +# 1#))
239        | otherwise              = error ("Prelude.Enum.Char.succ: bad argument")
240     pred (C# c#)
241        | not (ord# c# ==# 0#)   = C# (chr# (ord# c# -# 1#))
242        | otherwise              = error ("Prelude.Enum.Char.pred: bad argument")
243
244     toEnum   = chr
245     fromEnum = ord
246
247     {-# INLINE enumFrom #-}
248     enumFrom (C# x) = eftChar (ord# x) 0x10FFFF#
249         -- Blarg: technically I guess enumFrom isn't strict!
250
251     {-# INLINE enumFromTo #-}
252     enumFromTo (C# x) (C# y) = eftChar (ord# x) (ord# y)
253     
254     {-# INLINE enumFromThen #-}
255     enumFromThen (C# x1) (C# x2) = efdChar (ord# x1) (ord# x2)
256     
257     {-# INLINE enumFromThenTo #-}
258     enumFromThenTo (C# x1) (C# x2) (C# y) = efdtChar (ord# x1) (ord# x2) (ord# y)
259
260 {-# RULES
261 "eftChar"       [~1] forall x y.        eftChar x y       = build (\c n -> eftCharFB c n x y)
262 "efdChar"       [~1] forall x1 x2.      efdChar x1 x2     = build (\ c n -> efdCharFB c n x1 x2)
263 "efdtChar"      [~1] forall x1 x2 l.    efdtChar x1 x2 l  = build (\ c n -> efdtCharFB c n x1 x2 l)
264 "eftCharList"   [1]  eftCharFB  (:) [] = eftChar
265 "efdCharList"   [1]  efdCharFB  (:) [] = efdChar
266 "efdtCharList"  [1]  efdtCharFB (:) [] = efdtChar
267  #-}
268
269
270 -- We can do better than for Ints because we don't
271 -- have hassles about arithmetic overflow at maxBound
272 {-# INLINE [0] eftCharFB #-}
273 eftCharFB c n x y = go x
274                  where
275                     go x | x ># y    = n
276                          | otherwise = C# (chr# x) `c` go (x +# 1#)
277
278 eftChar x y | x ># y    = [] 
279                 | otherwise = C# (chr# x) : eftChar (x +# 1#) y
280
281
282 -- For enumFromThenTo we give up on inlining
283 {-# NOINLINE [0] efdCharFB #-}
284 efdCharFB c n x1 x2
285   | delta >=# 0# = go_up_char_fb c n x1 delta 0x10FFFF#
286   | otherwise    = go_dn_char_fb c n x1 delta 0#
287   where
288     delta = x2 -# x1
289
290 efdChar x1 x2
291   | delta >=# 0# = go_up_char_list x1 delta 0x10FFFF#
292   | otherwise    = go_dn_char_list x1 delta 0#
293   where
294     delta = x2 -# x1
295
296 {-# NOINLINE [0] efdtCharFB #-}
297 efdtCharFB c n x1 x2 lim
298   | delta >=# 0# = go_up_char_fb c n x1 delta lim
299   | otherwise    = go_dn_char_fb c n x1 delta lim
300   where
301     delta = x2 -# x1
302
303 efdtChar x1 x2 lim
304   | delta >=# 0# = go_up_char_list x1 delta lim
305   | otherwise    = go_dn_char_list x1 delta lim
306   where
307     delta = x2 -# x1
308
309 go_up_char_fb c n x delta lim
310   = go_up x
311   where
312     go_up x | x ># lim  = n
313             | otherwise = C# (chr# x) `c` go_up (x +# delta)
314
315 go_dn_char_fb c n x delta lim
316   = go_dn x
317   where
318     go_dn x | x <# lim  = n
319             | otherwise = C# (chr# x) `c` go_dn (x +# delta)
320
321 go_up_char_list x delta lim
322   = go_up x
323   where
324     go_up x | x ># lim  = []
325             | otherwise = C# (chr# x) : go_up (x +# delta)
326
327 go_dn_char_list x delta lim
328   = go_dn x
329   where
330     go_dn x | x <# lim  = []
331             | otherwise = C# (chr# x) : go_dn (x +# delta)
332 \end{code}
333
334
335 %*********************************************************
336 %*                                                      *
337 \subsection{Type @Int@}
338 %*                                                      *
339 %*********************************************************
340
341 Be careful about these instances.  
342         (a) remember that you have to count down as well as up e.g. [13,12..0]
343         (b) be careful of Int overflow
344         (c) remember that Int is bounded, so [1..] terminates at maxInt
345
346 Also NB that the Num class isn't available in this module.
347         
348 \begin{code}
349 instance  Bounded Int where
350     minBound =  minInt
351     maxBound =  maxInt
352
353 instance  Enum Int  where
354     succ x  
355        | x == maxBound  = error "Prelude.Enum.succ{Int}: tried to take `succ' of maxBound"
356        | otherwise      = x `plusInt` oneInt
357     pred x
358        | x == minBound  = error "Prelude.Enum.pred{Int}: tried to take `pred' of minBound"
359        | otherwise      = x `minusInt` oneInt
360
361     toEnum   x = x
362     fromEnum x = x
363
364     {-# INLINE enumFrom #-}
365     enumFrom (I# x) = eftInt x maxInt#
366         where I# maxInt# = maxInt
367         -- Blarg: technically I guess enumFrom isn't strict!
368
369     {-# INLINE enumFromTo #-}
370     enumFromTo (I# x) (I# y) = eftInt x y
371
372     {-# INLINE enumFromThen #-}
373     enumFromThen (I# x1) (I# x2) = efdInt x1 x2
374
375     {-# INLINE enumFromThenTo #-}
376     enumFromThenTo (I# x1) (I# x2) (I# y) = efdtInt x1 x2 y
377
378 {-# RULES
379 "eftInt"        [~1] forall x y.        eftInt x y       = build (\ c n -> eftIntFB c n x y)
380 "efdInt"        [~1] forall x1 x2.      efdInt x1 x2     = build (\ c n -> efdIntFB c n x1 x2)
381 "efdtInt"       [~1] forall x1 x2 l.    efdtInt x1 x2 l  = build (\ c n -> efdtIntFB c n x1 x2 l)
382
383 "eftIntList"    [1] eftIntFB  (:) [] = eftInt
384 "efdIntList"    [1] efdIntFB  (:) [] = efdInt
385 "efdtIntList"   [1] efdtIntFB (:) [] = efdtInt
386  #-}
387
388
389 {-# INLINE [0] eftIntFB #-}
390 eftIntFB c n x y | x ># y    = n        
391                  | otherwise = go x
392                  where
393                    go x = I# x `c` if x ==# y then n else go (x +# 1#)
394                         -- Watch out for y=maxBound; hence ==, not >
395         -- Be very careful not to have more than one "c"
396         -- so that when eftInfFB is inlined we can inline
397         -- whatver is bound to "c"
398
399 eftInt x y | x ># y    = []
400                | otherwise = go x
401                where
402                  go x = I# x : if x ==# y then [] else go (x +# 1#)
403
404
405 -- For enumFromThenTo we give up on inlining; so we don't worry
406 -- about duplicating occurrences of "c"
407 {-# NOINLINE [0] efdtIntFB #-}
408 efdtIntFB c n x1 x2 y
409   | delta >=# 0# = if x1 ># y then n else go_up_int_fb c n x1 delta lim
410   | otherwise    = if x1 <# y then n else go_dn_int_fb c n x1 delta lim 
411   where
412     delta = x2 -# x1
413     lim   = y -# delta
414
415 efdtInt x1 x2 y
416   | delta >=# 0# = if x1 ># y then [] else go_up_int_list x1 delta lim
417   | otherwise    = if x1 <# y then [] else go_dn_int_list x1 delta lim
418   where
419     delta = x2 -# x1
420     lim   = y -# delta
421
422 {-# NOINLINE [0] efdIntFB #-}
423 efdIntFB c n x1 x2
424   | delta >=# 0# = case maxInt of I# y -> go_up_int_fb c n x1 delta (y -# delta)
425   | otherwise    = case minInt of I# y -> go_dn_int_fb c n x1 delta (y -# delta)
426   where
427     delta = x2 -# x1
428
429 efdInt x1 x2
430   | delta >=# 0# = case maxInt of I# y -> go_up_int_list x1 delta (y -# delta)
431   | otherwise    = case minInt of I# y -> go_dn_int_list x1 delta (y -# delta)
432   where
433     delta = x2 -# x1
434
435 -- In all of these, the (x +# delta) is guaranteed not to overflow
436
437 go_up_int_fb c n x delta lim
438   = go_up x
439   where
440     go_up x | x ># lim  = I# x `c` n
441             | otherwise = I# x `c` go_up (x +# delta)
442
443 go_dn_int_fb c n x delta lim 
444   = go_dn x
445   where
446     go_dn x | x <# lim  = I# x `c` n
447             | otherwise = I# x `c` go_dn (x +# delta)
448
449 go_up_int_list x delta lim
450   = go_up x
451   where
452     go_up x | x ># lim  = [I# x]
453             | otherwise = I# x : go_up (x +# delta)
454
455 go_dn_int_list x delta lim 
456   = go_dn x
457   where
458     go_dn x | x <# lim  = [I# x]
459             | otherwise = I# x : go_dn (x +# delta)
460 \end{code}
461