3e3e72f0b67fdd580485e9167ec1ee1ec9968b89
[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 instance Eq Float where
105     (F# x) == (F# y) = x `eqFloat#` y
106
107 instance Eq Double where
108     (D# x) == (D# y) = x ==## y
109
110 -- | The 'Ord' class is used for totally ordered datatypes.
111 --
112 -- Instances of 'Ord' can be derived for any user-defined
113 -- datatype whose constituent types are in 'Ord'.  The declared order
114 -- of the constructors in the data declaration determines the ordering
115 -- in derived 'Ord' instances.  The 'Ordering' datatype allows a single
116 -- comparison to determine the precise ordering of two objects.
117 --
118 -- Minimal complete definition: either 'compare' or '<='.
119 -- Using 'compare' can be more efficient for complex types.
120 --
121 class  (Eq a) => Ord a  where
122     compare              :: a -> a -> Ordering
123     (<), (<=), (>), (>=) :: a -> a -> Bool
124     max, min             :: a -> a -> a
125
126     compare x y = if x == y then EQ
127                   -- NB: must be '<=' not '<' to validate the
128                   -- above claim about the minimal things that
129                   -- can be defined for an instance of Ord:
130                   else if x <= y then LT
131                   else GT
132
133     x <  y = case compare x y of { LT -> True;  _ -> False }
134     x <= y = case compare x y of { GT -> False; _ -> True }
135     x >  y = case compare x y of { GT -> True;  _ -> False }
136     x >= y = case compare x y of { LT -> False; _ -> True }
137
138         -- These two default methods use '<=' rather than 'compare'
139         -- because the latter is often more expensive
140     max x y = if x <= y then y else x
141     min x y = if x <= y then x else y
142
143 deriving instance Ord ()
144 deriving instance (Ord a, Ord b) => Ord (a, b)
145 deriving instance (Ord a, Ord b, Ord c) => Ord (a, b, c)
146 deriving instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d)
147 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e)
148 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f)
149                => Ord (a, b, c, d, e, f)
150 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g)
151                => Ord (a, b, c, d, e, f, g)
152 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
153                    Ord h)
154                => Ord (a, b, c, d, e, f, g, h)
155 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
156                    Ord h, Ord i)
157                => Ord (a, b, c, d, e, f, g, h, i)
158 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
159                    Ord h, Ord i, Ord j)
160                => Ord (a, b, c, d, e, f, g, h, i, j)
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)
163                => Ord (a, b, c, d, e, f, g, h, i, j, k)
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)
166                => Ord (a, b, c, d, e, f, g, h, i, j, k, l)
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)
169                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m)
170 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
171                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n)
172                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
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, Ord l, Ord m, Ord n, Ord o)
175                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
176
177 instance (Ord a) => Ord [a] where
178     {-# SPECIALISE instance Ord [Char] #-}
179     compare []     []     = EQ
180     compare []     (_:_)  = LT
181     compare (_:_)  []     = GT
182     compare (x:xs) (y:ys) = case compare x y of
183                                 EQ    -> compare xs ys
184                                 other -> other
185
186 deriving instance Ord Bool
187 deriving instance Ord Ordering
188
189 -- We don't use deriving for Ord Char, because for Ord the derived
190 -- instance defines only compare, which takes two primops.  Then
191 -- '>' uses compare, and therefore takes two primops instead of one.
192 instance Ord Char where
193     (C# c1) >  (C# c2) = c1 `gtChar#` c2
194     (C# c1) >= (C# c2) = c1 `geChar#` c2
195     (C# c1) <= (C# c2) = c1 `leChar#` c2
196     (C# c1) <  (C# c2) = c1 `ltChar#` c2
197
198 instance Ord Integer where
199     (<=) = leInteger
200     (>)  = gtInteger
201     (<)  = ltInteger
202     (>=) = geInteger
203     compare = compareInteger
204
205 instance Ord Float where
206     (F# x) `compare` (F# y)
207         = if      x `ltFloat#` y then LT
208           else if x `eqFloat#` y then EQ
209           else                        GT
210
211     (F# x) <  (F# y) = x `ltFloat#`  y
212     (F# x) <= (F# y) = x `leFloat#`  y
213     (F# x) >= (F# y) = x `geFloat#`  y
214     (F# x) >  (F# y) = x `gtFloat#`  y
215
216 instance Ord Double where
217     (D# x) `compare` (D# y)
218         = if      x <##  y then LT
219           else if x ==## y then EQ
220           else                  GT
221
222     (D# x) <  (D# y) = x <##  y
223     (D# x) <= (D# y) = x <=## y
224     (D# x) >= (D# y) = x >=## y
225     (D# x) >  (D# y) = x >##  y
226
227 -- OK, so they're technically not part of a class...:
228
229 -- Boolean functions
230
231 -- | Boolean \"and\"
232 (&&)                    :: Bool -> Bool -> Bool
233 True  && x              =  x
234 False && _              =  False
235
236 -- | Boolean \"or\"
237 (||)                    :: Bool -> Bool -> Bool
238 True  || _              =  True
239 False || x              =  x
240
241 -- | Boolean \"not\"
242 not                     :: Bool -> Bool
243 not True                =  False
244 not False               =  True
245