17d0f93e1b991a6873622869eda8741d6df8b4cd
[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
31 infix  4  ==, /=, <, <=, >=, >
32 infixr 3  &&
33 infixr 2  ||
34
35 default ()              -- Double isn't available yet
36
37 -- | The 'Eq' class defines equality ('==') and inequality ('/=').
38 -- All the basic datatypes exported by the "Prelude" are instances of 'Eq',
39 -- and 'Eq' may be derived for any datatype whose constituents are also
40 -- instances of 'Eq'.
41 --
42 -- Minimal complete definition: either '==' or '/='.
43 --
44 class  Eq a  where
45     (==), (/=)           :: a -> a -> Bool
46
47     {-# INLINE (/=) #-}
48     {-# INLINE (==) #-}
49     x /= y               = not (x == y)
50     x == y               = not (x /= y)
51
52 deriving instance Eq ()
53 deriving instance (Eq  a, Eq  b) => Eq  (a, b)
54 deriving instance (Eq  a, Eq  b, Eq  c) => Eq  (a, b, c)
55 deriving instance (Eq  a, Eq  b, Eq  c, Eq  d) => Eq  (a, b, c, d)
56 deriving instance (Eq  a, Eq  b, Eq  c, Eq  d, Eq  e) => Eq  (a, b, c, d, e)
57 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f)
58                => Eq (a, b, c, d, e, f)
59 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g)
60                => Eq (a, b, c, d, e, f, g)
61 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
62                    Eq h)
63                => Eq (a, b, c, d, e, f, g, h)
64 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
65                    Eq h, Eq i)
66                => Eq (a, b, c, d, e, f, g, h, i)
67 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
68                    Eq h, Eq i, Eq j)
69                => Eq (a, b, c, d, e, f, g, h, i, j)
70 deriving instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g,
71                    Eq h, Eq i, Eq j, Eq k)
72                => Eq (a, b, c, d, e, f, g, h, i, j, k)
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, Eq l)
75                => Eq (a, b, c, d, e, f, g, h, i, j, k, l)
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, Eq m)
78                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m)
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, Eq n)
81                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
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, Eq o)
84                => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
85
86 instance (Eq a) => Eq [a] where
87     {-# SPECIALISE instance Eq [Char] #-}
88     []     == []     = True
89     (x:xs) == (y:ys) = x == y && xs == ys
90     _xs    == _ys    = False
91
92 deriving instance Eq Bool
93 deriving instance Eq Ordering
94
95 instance Eq Char where
96     (C# c1) == (C# c2) = c1 `eqChar#` c2
97     (C# c1) /= (C# c2) = c1 `neChar#` c2
98
99 instance  Eq Integer  where
100     (==) = eqInteger
101     (/=) = neqInteger
102
103 instance Eq Float where
104     (F# x) == (F# y) = x `eqFloat#` y
105
106 instance Eq Double where
107     (D# x) == (D# y) = x ==## y
108
109 -- | The 'Ord' class is used for totally ordered datatypes.
110 --
111 -- Instances of 'Ord' can be derived for any user-defined
112 -- datatype whose constituent types are in 'Ord'.  The declared order
113 -- of the constructors in the data declaration determines the ordering
114 -- in derived 'Ord' instances.  The 'Ordering' datatype allows a single
115 -- comparison to determine the precise ordering of two objects.
116 --
117 -- Minimal complete definition: either 'compare' or '<='.
118 -- Using 'compare' can be more efficient for complex types.
119 --
120 class  (Eq a) => Ord a  where
121     compare              :: a -> a -> Ordering
122     (<), (<=), (>), (>=) :: a -> a -> Bool
123     max, min             :: a -> a -> a
124
125     compare x y = if x == y then EQ
126                   -- NB: must be '<=' not '<' to validate the
127                   -- above claim about the minimal things that
128                   -- can be defined for an instance of Ord:
129                   else if x <= y then LT
130                   else GT
131
132     x <  y = case compare x y of { LT -> True;  _ -> False }
133     x <= y = case compare x y of { GT -> False; _ -> True }
134     x >  y = case compare x y of { GT -> True;  _ -> False }
135     x >= y = case compare x y of { LT -> False; _ -> True }
136
137         -- These two default methods use '<=' rather than 'compare'
138         -- because the latter is often more expensive
139     max x y = if x <= y then y else x
140     min x y = if x <= y then x else y
141
142 deriving instance Ord ()
143 deriving instance (Ord a, Ord b) => Ord (a, b)
144 deriving instance (Ord a, Ord b, Ord c) => Ord (a, b, c)
145 deriving instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d)
146 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e)
147 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f)
148                => Ord (a, b, c, d, e, f)
149 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g)
150                => Ord (a, b, c, d, e, f, g)
151 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
152                    Ord h)
153                => Ord (a, b, c, d, e, f, g, h)
154 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
155                    Ord h, Ord i)
156                => Ord (a, b, c, d, e, f, g, h, i)
157 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
158                    Ord h, Ord i, Ord j)
159                => Ord (a, b, c, d, e, f, g, h, i, j)
160 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
161                    Ord h, Ord i, Ord j, Ord k)
162                => Ord (a, b, c, d, e, f, g, h, i, j, k)
163 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
164                    Ord h, Ord i, Ord j, Ord k, Ord l)
165                => Ord (a, b, c, d, e, f, g, h, i, j, k, l)
166 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
167                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m)
168                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m)
169 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
170                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n)
171                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
172 deriving instance (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g,
173                    Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o)
174                => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
175
176 instance (Ord a) => Ord [a] where
177     {-# SPECIALISE instance Ord [Char] #-}
178     compare []     []     = EQ
179     compare []     (_:_)  = LT
180     compare (_:_)  []     = GT
181     compare (x:xs) (y:ys) = case compare x y of
182                                 EQ    -> compare xs ys
183                                 other -> other
184
185 deriving instance Ord Bool
186 deriving instance Ord Ordering
187
188 -- We don't use deriving for Ord Char, because for Ord the derived
189 -- instance defines only compare, which takes two primops.  Then
190 -- '>' uses compare, and therefore takes two primops instead of one.
191 instance Ord Char where
192     (C# c1) >  (C# c2) = c1 `gtChar#` c2
193     (C# c1) >= (C# c2) = c1 `geChar#` c2
194     (C# c1) <= (C# c2) = c1 `leChar#` c2
195     (C# c1) <  (C# c2) = c1 `ltChar#` c2
196
197 instance Ord Integer where
198     (<=) = leInteger
199     (>)  = gtInteger
200     (<)  = ltInteger
201     (>=) = geInteger
202     compare = compareInteger
203
204 instance Ord Float where
205     (F# x) `compare` (F# y)
206         = if      x `ltFloat#` y then LT
207           else if x `eqFloat#` y then EQ
208           else                        GT
209
210     (F# x) <  (F# y) = x `ltFloat#`  y
211     (F# x) <= (F# y) = x `leFloat#`  y
212     (F# x) >= (F# y) = x `geFloat#`  y
213     (F# x) >  (F# y) = x `gtFloat#`  y
214
215 instance Ord Double where
216     (D# x) `compare` (D# y)
217         = if      x <##  y then LT
218           else if x ==## y then EQ
219           else                  GT
220
221     (D# x) <  (D# y) = x <##  y
222     (D# x) <= (D# y) = x <=## y
223     (D# x) >= (D# y) = x >=## y
224     (D# x) >  (D# y) = x >##  y
225
226 -- OK, so they're technically not part of a class...:
227
228 -- Boolean functions
229
230 -- | Boolean \"and\"
231 (&&)                    :: Bool -> Bool -> Bool
232 True  && x              =  x
233 False && _              =  False
234
235 -- | Boolean \"or\"
236 (||)                    :: Bool -> Bool -> Bool
237 True  || _              =  True
238 False || x              =  x
239
240 -- | Boolean \"not\"
241 not                     :: Bool -> Bool
242 not True                =  False
243 not False               =  True
244