De-orphan the Eq/Ord Integer instances
[ghc-base.git] / GHC / Classes.hs
1
2 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
3 {-# OPTIONS_GHC -fno-warn-unused-imports #-}
4 -- XXX -fno-warn-unused-imports needed for the GHC.Tuple import below. Sigh.
5 {-# OPTIONS_HADDOCK hide #-}
6 -----------------------------------------------------------------------------
7 -- |
8 -- Module      :  GHC.Classes
9 -- Copyright   :  (c) The University of Glasgow, 1992-2002
10 -- License     :  see libraries/base/LICENSE
11 --
12 -- Maintainer  :  cvs-ghc@haskell.org
13 -- Stability   :  internal
14 -- Portability :  non-portable (GHC extensions)
15 --
16 -- Basic classes.
17 --
18 -----------------------------------------------------------------------------
19
20 module GHC.Classes where
21
22 import GHC.Bool
23 import GHC.Integer
24 -- GHC.Magic is used in some derived instances
25 import GHC.Magic ()
26 import GHC.Ordering
27 import GHC.Prim
28 import GHC.Tuple
29 import GHC.Types
30 import GHC.Unit
31
32 infix  4  ==, /=, <, <=, >=, >
33 infixr 3  &&
34 infixr 2  ||
35
36 default ()              -- Double isn't available yet
37
38 -- | The 'Eq' class defines equality ('==') and inequality ('/=').
39 -- All the basic datatypes exported by the "Prelude" are instances of 'Eq',
40 -- and 'Eq' may be derived for any datatype whose constituents are also
41 -- instances of 'Eq'.
42 --
43 -- Minimal complete definition: either '==' or '/='.
44 --
45 class  Eq a  where
46     (==), (/=)           :: a -> a -> Bool
47
48     {-# INLINE (/=) #-}
49     {-# INLINE (==) #-}
50     x /= y               = not (x == y)
51     x == y               = not (x /= y)
52
53 deriving instance Eq ()
54 deriving instance (Eq  a, Eq  b) => Eq  (a, b)
55 deriving instance (Eq  a, Eq  b, Eq  c) => Eq  (a, b, c)
56 deriving instance (Eq  a, Eq  b, Eq  c, Eq  d) => Eq  (a, b, c, d)
57 deriving instance (Eq  a, Eq  b, Eq  c, Eq  d, Eq  e) => Eq  (a, b, c, d, e)
58 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f)
59                => Eq (a, b, c, d, e, f)
60 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g)
61                => Eq (a, b, c, d, e, f, g)
62 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
63                    Eq h)
64                => Eq (a, b, c, d, e, f, g, h)
65 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
66                    Eq h, Eq i)
67                => Eq (a, b, c, d, e, f, g, h, i)
68 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
69                    Eq h, Eq i, Eq j)
70                => Eq (a, b, c, d, e, f, g, h, i, j)
71 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
72                    Eq h, Eq i, Eq j, Eq k)
73                => Eq (a, b, c, d, e, f, g, h, i, j, k)
74 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
75                    Eq h, Eq i, Eq j, Eq k, Eq l)
76                => Eq (a, b, c, d, e, f, g, h, i, j, k, l)
77 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
78                    Eq h, Eq i, Eq j, Eq k, Eq l, Eq m)
79                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m)
80 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
81                    Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n)
82                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
83 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
84                    Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o)
85                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
86
87 instance (Eq a) => Eq [a] where
88     {-# SPECIALISE instance Eq [Char] #-}
89     []     == []     = True
90     (x:xs) == (y:ys) = x == y && xs == ys
91     _xs    == _ys    = False
92
93 deriving instance Eq Bool
94 deriving instance Eq Ordering
95
96 instance Eq Char where
97     (C# c1) == (C# c2) = c1 `eqChar#` c2
98     (C# c1) /= (C# c2) = c1 `neChar#` c2
99
100 instance  Eq Integer  where
101     (==) = eqInteger
102     (/=) = neqInteger
103
104 -- | The 'Ord' class is used for totally ordered datatypes.
105 --
106 -- Instances of 'Ord' can be derived for any user-defined
107 -- datatype whose constituent types are in 'Ord'.  The declared order
108 -- of the constructors in the data declaration determines the ordering
109 -- in derived 'Ord' instances.  The 'Ordering' datatype allows a single
110 -- comparison to determine the precise ordering of two objects.
111 --
112 -- Minimal complete definition: either 'compare' or '<='.
113 -- Using 'compare' can be more efficient for complex types.
114 --
115 class  (Eq a) => Ord a  where
116     compare              :: a -> a -> Ordering
117     (<), (<=), (>), (>=) :: a -> a -> Bool
118     max, min             :: a -> a -> a
119
120     compare x y = if x == y then EQ
121                   -- NB: must be '<=' not '<' to validate the
122                   -- above claim about the minimal things that
123                   -- can be defined for an instance of Ord:
124                   else if x <= y then LT
125                   else GT
126
127     x <  y = case compare x y of { LT -> True;  _ -> False }
128     x <= y = case compare x y of { GT -> False; _ -> True }
129     x >  y = case compare x y of { GT -> True;  _ -> False }
130     x >= y = case compare x y of { LT -> False; _ -> True }
131
132         -- These two default methods use '<=' rather than 'compare'
133         -- because the latter is often more expensive
134     max x y = if x <= y then y else x
135     min x y = if x <= y then x else y
136
137 deriving instance Ord ()
138 deriving instance (Ord a, Ord b) => Ord (a, b)
139 deriving instance (Ord a, Ord b, Ord c) => Ord (a, b, c)
140 deriving instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d)
141 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e)
142 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f)
143                => Ord (a, b, c, d, e, f)
144 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g)
145                => Ord (a, b, c, d, e, f, g)
146 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
147                    Ord h)
148                => Ord (a, b, c, d, e, f, g, h)
149 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
150                    Ord h, Ord i)
151                => Ord (a, b, c, d, e, f, g, h, i)
152 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
153                    Ord h, Ord i, Ord j)
154                => Ord (a, b, c, d, e, f, g, h, i, j)
155 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
156                    Ord h, Ord i, Ord j, Ord k)
157                => Ord (a, b, c, d, e, f, g, h, i, j, k)
158 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
159                    Ord h, Ord i, Ord j, Ord k, Ord l)
160                => Ord (a, b, c, d, e, f, g, h, i, j, k, l)
161 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
162                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m)
163                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m)
164 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
165                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n)
166                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
167 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
168                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o)
169                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
170
171 instance (Ord a) => Ord [a] where
172     {-# SPECIALISE instance Ord [Char] #-}
173     compare []     []     = EQ
174     compare []     (_:_)  = LT
175     compare (_:_)  []     = GT
176     compare (x:xs) (y:ys) = case compare x y of
177                                 EQ    -> compare xs ys
178                                 other -> other
179
180 deriving instance Ord Bool
181 deriving instance Ord Ordering
182
183 -- We don't use deriving for Ord Char, because for Ord the derived
184 -- instance defines only compare, which takes two primops.  Then
185 -- '>' uses compare, and therefore takes two primops instead of one.
186 instance Ord Char where
187     (C# c1) >  (C# c2) = c1 `gtChar#` c2
188     (C# c1) >= (C# c2) = c1 `geChar#` c2
189     (C# c1) <= (C# c2) = c1 `leChar#` c2
190     (C# c1) <  (C# c2) = c1 `ltChar#` c2
191
192 instance Ord Integer where
193     (<=) = leInteger
194     (>)  = gtInteger
195     (<)  = ltInteger
196     (>=) = geInteger
197     compare = compareInteger
198
199 -- OK, so they're technically not part of a class...:
200
201 -- Boolean functions
202
203 -- | Boolean \"and\"
204 (&&)                    :: Bool -> Bool -> Bool
205 True  && x              =  x
206 False && _              =  False
207
208 -- | Boolean \"or\"
209 (||)                    :: Bool -> Bool -> Bool
210 True  || _              =  True
211 False || x              =  x
212
213 -- | Boolean \"not\"
214 not                     :: Bool -> Bool
215 not True                =  False
216 not False               =  True
217