File: Enum.hs

package info (click to toggle)
bali-phy 4.0~beta16%2Bdfsg-1
  • links: PTS, VCS
  • area: main
  • in suites: experimental
  • size: 15,192 kB
  • sloc: cpp: 119,288; xml: 13,482; haskell: 9,722; python: 2,930; yacc: 1,329; perl: 1,169; lex: 904; sh: 343; makefile: 26
file content (102 lines) | stat: -rw-r--r-- 2,944 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
{-# LANGUAGE NoImplicitPrelude #-}
module Compiler.Enum (Enum(..),
                      enumFrom,
                      enumFromThen,
                      enumFromTo,
                      enumFromThenTo)
    where


import Compiler.Num   -- for -,+
import Compiler.Error -- for error
import Data.Ord       -- for <=
import Data.Bool      -- for otherwise

class Bounded a where
    minBound :: a
    maxBound :: a

class Enum a where
    succ :: a -> a
    pred :: a -> a
    toEnum :: Int -> a
    fromEnum :: a -> Int
    enumFrom :: a -> [a]
    enumFromThen :: a -> a -> [a]
    enumFromTo   :: a -> a -> [a]
    enumFromThenTo :: a -> a -> a -> [a]

    -- This may wrap instead of throwing an exception on succ maxBound, pred minBound.
    succ x = toEnum (fromEnum x + 1)
    pred x = toEnum (fromEnum x - 1)

    enumFrom n = n:enumFrom (succ n)

    enumFromTo n m | fromEnum n <= fromEnum m     = n : enumFromTo (succ n) m
                   | otherwise                    = []

    enumFromThen n n' = n : n' : worker (f x) (f x n') where
             worker s v = v : worker s (s v)
             x = fromEnum n' - fromEnum n
             f n y  | n > 0 = f (n - 1) (succ y)
                    | n < 0 = f (n + 1) (pred y)
                    | otherwise = y

    enumFromThenTo n n' m = worker (f x) (c x) n m where
             x = fromEnum n' - fromEnum n
             c x = bool (>=) (<=) (x > 0)
             f n y | n > 0      = f (n - 1) (succ y)
                   | n < 0      = f (n + 1) (pred y)
                   | otherwise  = y
             worker s c v m | c (fromEnum v) (fromEnum m)      = v : worker s c (s v) m
                            | otherwise  = []

instance Enum Char where
    toEnum n = intToChar n
    fromEnum n = charToInt n
    succ x = x + 1
    pred x = x - 1

    enumFromThen from next = enumByFrom (next-from) from

    enumFromThenTo from next to = enumByToFrom (next - from) to from

instance Enum Int where
    toEnum n = n
    fromEnum n = n
    succ x = x + 1
    pred x = x - 1

    enumFromThen from next = enumByFrom (next-from) from

    enumFromThenTo from next to = enumByToFrom (next - from) to from

instance Enum Integer where
    toEnum n = intToInteger n
    fromEnum n = integerToInt n
    succ x = x + 1
    pred x = x - 1

    enumFromThen from next = enumByFrom (next-from) from

    enumFromThenTo from next to = enumByToFrom (next - from) to from

instance Enum Double where
    toEnum n = intToDouble n
    fromEnum x = doubleToInt x
    succ x = x + 1
    pred x = x - 1

    enumFromThen from next = enumByFrom (next-from) from

    enumFromThenTo from next to = enumByToFrom (next - from) to from

-- This isn't a standard function -- I made it up..
enumByFrom by from = from:enumByFrom by (from+by)

-- This isn't right for negative "by"
enumByToFrom by to from | from <= to    = from:enumByToFrom by to (from+by)
                        | otherwise     = []