add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / Classes.hs
1
2 {-# LANGUAGE NoImplicitPrelude, MagicHash, StandaloneDeriving #-}
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.Integer
23 -- GHC.Magic is used in some derived instances
24 import GHC.Magic ()
25 import GHC.Ordering
26 import GHC.Prim
27 import GHC.Tuple
28 import GHC.Types
29 import GHC.Unit
30 -- For defining instances for the generic deriving mechanism
31 import GHC.Generics (Arity(..), Associativity(..), Fixity(..))
32
33
34 infix  4  ==, /=, <, <=, >=, >
35 infixr 3  &&
36 infixr 2  ||
37
38 default ()              -- Double isn't available yet
39
40 -- | The 'Eq' class defines equality ('==') and inequality ('/=').
41 -- All the basic datatypes exported by the "Prelude" are instances of 'Eq',
42 -- and 'Eq' may be derived for any datatype whose constituents are also
43 -- instances of 'Eq'.
44 --
45 -- Minimal complete definition: either '==' or '/='.
46 --
47 class  Eq a  where
48     (==), (/=)           :: a -> a -> Bool
49
50     {-# INLINE (/=) #-}
51     {-# INLINE (==) #-}
52     x /= y               = not (x == y)
53     x == y               = not (x /= y)
54
55 deriving instance Eq ()
56 deriving instance (Eq  a, Eq  b) => Eq  (a, b)
57 deriving instance (Eq  a, Eq  b, Eq  c) => Eq  (a, b, c)
58 deriving instance (Eq  a, Eq  b, Eq  c, Eq  d) => Eq  (a, b, c, d)
59 deriving instance (Eq  a, Eq  b, Eq  c, Eq  d, Eq  e) => Eq  (a, b, c, d, e)
60 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f)
61                => Eq (a, b, c, d, e, f)
62 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g)
63                => Eq (a, b, c, d, e, f, g)
64 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
65                    Eq h)
66                => Eq (a, b, c, d, e, f, g, h)
67 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
68                    Eq h, Eq i)
69                => Eq (a, b, c, d, e, f, g, h, i)
70 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
71                    Eq h, Eq i, Eq j)
72                => Eq (a, b, c, d, e, f, g, h, i, j)
73 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
74                    Eq h, Eq i, Eq j, Eq k)
75                => Eq (a, b, c, d, e, f, g, h, i, j, k)
76 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
77                    Eq h, Eq i, Eq j, Eq k, Eq l)
78                => Eq (a, b, c, d, e, f, g, h, i, j, k, l)
79 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
80                    Eq h, Eq i, Eq j, Eq k, Eq l, Eq m)
81                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m)
82 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
83                    Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n)
84                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
85 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
86                    Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o)
87                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
88
89 instance (Eq a) => Eq [a] where
90     {-# SPECIALISE instance Eq [Char] #-}
91     []     == []     = True
92     (x:xs) == (y:ys) = x == y && xs == ys
93     _xs    == _ys    = False
94
95 deriving instance Eq Bool
96 deriving instance Eq Ordering
97
98 instance Eq Char where
99     (C# c1) == (C# c2) = c1 `eqChar#` c2
100     (C# c1) /= (C# c2) = c1 `neChar#` c2
101
102 instance  Eq Integer  where
103     (==) = eqInteger
104     (/=) = neqInteger
105
106 instance Eq Float where
107     (F# x) == (F# y) = x `eqFloat#` y
108
109 instance Eq Double where
110     (D# x) == (D# y) = x ==## y
111
112 instance Eq Int where
113     (==) = eqInt
114     (/=) = neInt
115
116 {-# INLINE eqInt #-}
117 {-# INLINE neInt #-}
118 eqInt, neInt :: Int -> Int -> Bool
119 (I# x) `eqInt` (I# y) = x ==# y
120 (I# x) `neInt` (I# y) = x /=# y
121
122 -- | The 'Ord' class is used for totally ordered datatypes.
123 --
124 -- Instances of 'Ord' can be derived for any user-defined
125 -- datatype whose constituent types are in 'Ord'.  The declared order
126 -- of the constructors in the data declaration determines the ordering
127 -- in derived 'Ord' instances.  The 'Ordering' datatype allows a single
128 -- comparison to determine the precise ordering of two objects.
129 --
130 -- Minimal complete definition: either 'compare' or '<='.
131 -- Using 'compare' can be more efficient for complex types.
132 --
133 class  (Eq a) => Ord a  where
134     compare              :: a -> a -> Ordering
135     (<), (<=), (>), (>=) :: a -> a -> Bool
136     max, min             :: a -> a -> a
137
138     compare x y = if x == y then EQ
139                   -- NB: must be '<=' not '<' to validate the
140                   -- above claim about the minimal things that
141                   -- can be defined for an instance of Ord:
142                   else if x <= y then LT
143                   else GT
144
145     x <  y = case compare x y of { LT -> True;  _ -> False }
146     x <= y = case compare x y of { GT -> False; _ -> True }
147     x >  y = case compare x y of { GT -> True;  _ -> False }
148     x >= y = case compare x y of { LT -> False; _ -> True }
149
150         -- These two default methods use '<=' rather than 'compare'
151         -- because the latter is often more expensive
152     max x y = if x <= y then y else x
153     min x y = if x <= y then x else y
154
155 deriving instance Ord ()
156 deriving instance (Ord a, Ord b) => Ord (a, b)
157 deriving instance (Ord a, Ord b, Ord c) => Ord (a, b, c)
158 deriving instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d)
159 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e)
160 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f)
161                => Ord (a, b, c, d, e, f)
162 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g)
163                => Ord (a, b, c, d, e, f, g)
164 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
165                    Ord h)
166                => Ord (a, b, c, d, e, f, g, h)
167 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
168                    Ord h, Ord i)
169                => Ord (a, b, c, d, e, f, g, h, i)
170 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
171                    Ord h, Ord i, Ord j)
172                => Ord (a, b, c, d, e, f, g, h, i, j)
173 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
174                    Ord h, Ord i, Ord j, Ord k)
175                => Ord (a, b, c, d, e, f, g, h, i, j, k)
176 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
177                    Ord h, Ord i, Ord j, Ord k, Ord l)
178                => Ord (a, b, c, d, e, f, g, h, i, j, k, l)
179 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
180                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m)
181                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m)
182 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
183                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n)
184                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
185 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
186                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o)
187                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
188
189 instance (Ord a) => Ord [a] where
190     {-# SPECIALISE instance Ord [Char] #-}
191     compare []     []     = EQ
192     compare []     (_:_)  = LT
193     compare (_:_)  []     = GT
194     compare (x:xs) (y:ys) = case compare x y of
195                                 EQ    -> compare xs ys
196                                 other -> other
197
198 deriving instance Ord Bool
199 deriving instance Ord Ordering
200
201 -- We don't use deriving for Ord Char, because for Ord the derived
202 -- instance defines only compare, which takes two primops.  Then
203 -- '>' uses compare, and therefore takes two primops instead of one.
204 instance Ord Char where
205     (C# c1) >  (C# c2) = c1 `gtChar#` c2
206     (C# c1) >= (C# c2) = c1 `geChar#` c2
207     (C# c1) <= (C# c2) = c1 `leChar#` c2
208     (C# c1) <  (C# c2) = c1 `ltChar#` c2
209
210 instance Ord Integer where
211     (<=) = leInteger
212     (>)  = gtInteger
213     (<)  = ltInteger
214     (>=) = geInteger
215     compare = compareInteger
216
217 instance Ord Float where
218     (F# x) `compare` (F# y)
219         = if      x `ltFloat#` y then LT
220           else if x `eqFloat#` y then EQ
221           else                        GT
222
223     (F# x) <  (F# y) = x `ltFloat#`  y
224     (F# x) <= (F# y) = x `leFloat#`  y
225     (F# x) >= (F# y) = x `geFloat#`  y
226     (F# x) >  (F# y) = x `gtFloat#`  y
227
228 instance Ord Double where
229     (D# x) `compare` (D# y)
230         = if      x <##  y then LT
231           else if x ==## y then EQ
232           else                  GT
233
234     (D# x) <  (D# y) = x <##  y
235     (D# x) <= (D# y) = x <=## y
236     (D# x) >= (D# y) = x >=## y
237     (D# x) >  (D# y) = x >##  y
238
239 instance Ord Int where
240     compare = compareInt
241     (<)     = ltInt
242     (<=)    = leInt
243     (>=)    = geInt
244     (>)     = gtInt
245
246 {-# INLINE gtInt #-}
247 {-# INLINE geInt #-}
248 {-# INLINE ltInt #-}
249 {-# INLINE leInt #-}
250 gtInt, geInt, ltInt, leInt :: Int -> Int -> Bool
251 (I# x) `gtInt` (I# y) = x >#  y
252 (I# x) `geInt` (I# y) = x >=# y
253 (I# x) `ltInt` (I# y) = x <#  y
254 (I# x) `leInt` (I# y) = x <=# y
255
256 compareInt :: Int -> Int -> Ordering
257 (I# x#) `compareInt` (I# y#) = compareInt# x# y#
258
259 compareInt# :: Int# -> Int# -> Ordering
260 compareInt# x# y#
261     | x# <#  y# = LT
262     | x# ==# y# = EQ
263     | True      = GT
264
265 -- OK, so they're technically not part of a class...:
266
267 -- Boolean functions
268
269 -- | Boolean \"and\"
270 (&&)                    :: Bool -> Bool -> Bool
271 True  && x              =  x
272 False && _              =  False
273
274 -- | Boolean \"or\"
275 (||)                    :: Bool -> Bool -> Bool
276 True  || _              =  True
277 False || x              =  x
278
279 -- | Boolean \"not\"
280 not                     :: Bool -> Bool
281 not True                =  False
282 not False               =  True
283
284
285 ------------------------------------------------------------------------
286 -- Generic deriving
287 ------------------------------------------------------------------------
288
289 -- We need instances for some basic datatypes, but some of those use Int,
290 -- so we have to put the instances here
291 deriving instance Eq Arity
292 deriving instance Eq Associativity
293 deriving instance Eq Fixity
294
295 deriving instance Ord Arity
296 deriving instance Ord Associativity
297 deriving instance Ord Fixity