Eq and Ord have moved into GHC.Classes
authorIan Lynagh <igloo@earth.li>
Thu, 7 Aug 2008 09:53:52 +0000 (09:53 +0000)
committerIan Lynagh <igloo@earth.li>
Thu, 7 Aug 2008 09:53:52 +0000 (09:53 +0000)
Data/Tuple.hs
GHC/Base.lhs
GHC/Classes.hs [new file with mode: 0644]
base.cabal

index 8ed3928..81ae83d 100644 (file)
@@ -40,7 +40,9 @@ module Data.Tuple
     where
 
 #ifdef __GLASGOW_HASKELL__
-import GHC.Base
+import GHC.Bool
+import GHC.Classes
+import GHC.Ordering
 -- XXX The standalone deriving clauses fail with
 --     The data constructors of `(,)' are not all in scope
 --       so you cannot derive an instance for it
index 5eb4314..0e5c4d2 100644 (file)
@@ -85,6 +85,7 @@ module GHC.Base
         (
         module GHC.Base,
         module GHC.Bool,
+        module GHC.Classes,
         module GHC.Generics,
         module GHC.Ordering,
         module GHC.Types,
@@ -95,6 +96,7 @@ module GHC.Base
 
 import GHC.Types
 import GHC.Bool
+import GHC.Classes
 import GHC.Generics
 import GHC.Ordering
 import GHC.Prim
@@ -102,9 +104,6 @@ import {-# SOURCE #-} GHC.Err
 
 infixr 9  .
 infixr 5  ++
-infix  4  ==, /=, <, <=, >=, >
-infixr 3  &&
-infixr 2  ||
 infixl 1  >>, >>=
 infixr 0  $
 
@@ -150,61 +149,6 @@ unpackCStringUtf8# a = error "urk"
 
 %*********************************************************
 %*                                                      *
-\subsection{Standard classes @Eq@, @Ord@}
-%*                                                      *
-%*********************************************************
-
-\begin{code}
-
--- | The 'Eq' class defines equality ('==') and inequality ('/=').
--- All the basic datatypes exported by the "Prelude" are instances of 'Eq',
--- and 'Eq' may be derived for any datatype whose constituents are also
--- instances of 'Eq'.
---
--- Minimal complete definition: either '==' or '/='.
---
-class  Eq a  where
-    (==), (/=)           :: a -> a -> Bool
-
-    x /= y               = not (x == y)
-    x == y               = not (x /= y)
-
--- | The 'Ord' class is used for totally ordered datatypes.
---
--- Instances of 'Ord' can be derived for any user-defined
--- datatype whose constituent types are in 'Ord'.  The declared order
--- of the constructors in the data declaration determines the ordering
--- in derived 'Ord' instances.  The 'Ordering' datatype allows a single
--- comparison to determine the precise ordering of two objects.
---
--- Minimal complete definition: either 'compare' or '<='.
--- Using 'compare' can be more efficient for complex types.
---
-class  (Eq a) => Ord a  where
-    compare              :: a -> a -> Ordering
-    (<), (<=), (>), (>=) :: a -> a -> Bool
-    max, min             :: a -> a -> a
-
-    compare x y
-        | x == y    = EQ
-        | x <= y    = LT        -- NB: must be '<=' not '<' to validate the
-                                -- above claim about the minimal things that
-                                -- can be defined for an instance of Ord
-        | otherwise = GT
-
-    x <  y = case compare x y of { LT -> True;  _other -> False }
-    x <= y = case compare x y of { GT -> False; _other -> True }
-    x >  y = case compare x y of { GT -> True;  _other -> False }
-    x >= y = case compare x y of { LT -> False; _other -> True }
-
-        -- These two default methods use '<=' rather than 'compare'
-        -- because the latter is often more expensive
-    max x y = if x <= y then y else x
-    min x y = if x <= y then x else y
-\end{code}
-
-%*********************************************************
-%*                                                      *
 \subsection{Monadic classes @Functor@, @Monad@ }
 %*                                                      *
 %*********************************************************
@@ -495,23 +439,6 @@ instance Ord Bool where
 
 -- Read is in GHC.Read, Show in GHC.Show
 
--- Boolean functions
-
--- | Boolean \"and\"
-(&&)                    :: Bool -> Bool -> Bool
-True  && x              =  x
-False && _              =  False
-
--- | Boolean \"or\"
-(||)                    :: Bool -> Bool -> Bool
-True  || _              =  True
-False || x              =  x
-
--- | Boolean \"not\"
-not                     :: Bool -> Bool
-not True                =  False
-not False               =  True
-
 -- |'otherwise' is defined as the value 'True'.  It helps to make
 -- guards more readable.  eg.
 --
diff --git a/GHC/Classes.hs b/GHC/Classes.hs
new file mode 100644 (file)
index 0000000..1638456
--- /dev/null
@@ -0,0 +1,93 @@
+
+{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+{-# OPTIONS_HADDOCK hide #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  GHC.Classes
+-- Copyright   :  (c) The University of Glasgow, 1992-2002
+-- License     :  see libraries/base/LICENSE
+--
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- Basic classes.
+--
+-----------------------------------------------------------------------------
+
+module GHC.Classes where
+
+import GHC.Bool
+import GHC.Ordering
+
+infix  4  ==, /=, <, <=, >=, >
+infixr 3  &&
+infixr 2  ||
+
+default ()              -- Double isn't available yet
+
+-- | The 'Eq' class defines equality ('==') and inequality ('/=').
+-- All the basic datatypes exported by the "Prelude" are instances of 'Eq',
+-- and 'Eq' may be derived for any datatype whose constituents are also
+-- instances of 'Eq'.
+--
+-- Minimal complete definition: either '==' or '/='.
+--
+class  Eq a  where
+    (==), (/=)           :: a -> a -> Bool
+
+    x /= y               = not (x == y)
+    x == y               = not (x /= y)
+
+-- | The 'Ord' class is used for totally ordered datatypes.
+--
+-- Instances of 'Ord' can be derived for any user-defined
+-- datatype whose constituent types are in 'Ord'.  The declared order
+-- of the constructors in the data declaration determines the ordering
+-- in derived 'Ord' instances.  The 'Ordering' datatype allows a single
+-- comparison to determine the precise ordering of two objects.
+--
+-- Minimal complete definition: either 'compare' or '<='.
+-- Using 'compare' can be more efficient for complex types.
+--
+class  (Eq a) => Ord a  where
+    compare              :: a -> a -> Ordering
+    (<), (<=), (>), (>=) :: a -> a -> Bool
+    max, min             :: a -> a -> a
+
+    compare x y = if x == y then EQ
+                  -- NB: must be '<=' not '<' to validate the
+                  -- above claim about the minimal things that
+                  -- can be defined for an instance of Ord:
+                  else if x <= y then LT
+                  else GT
+
+    x <  y = case compare x y of { LT -> True;  _ -> False }
+    x <= y = case compare x y of { GT -> False; _ -> True }
+    x >  y = case compare x y of { GT -> True;  _ -> False }
+    x >= y = case compare x y of { LT -> False; _ -> True }
+
+        -- These two default methods use '<=' rather than 'compare'
+        -- because the latter is often more expensive
+    max x y = if x <= y then y else x
+    min x y = if x <= y then x else y
+
+-- OK, so they're technically not part of a class...:
+
+-- Boolean functions
+
+-- | Boolean \"and\"
+(&&)                    :: Bool -> Bool -> Bool
+True  && x              =  x
+False && _              =  False
+
+-- | Boolean \"or\"
+(||)                    :: Bool -> Bool -> Bool
+True  || _              =  True
+False || x              =  x
+
+-- | Boolean \"not\"
+not                     :: Bool -> Bool
+not True                =  False
+not False               =  True
+
index 05fd3e7..42a232d 100644 (file)
@@ -29,6 +29,7 @@ Library {
             Foreign.Concurrent,
             GHC.Arr,
             GHC.Base,
+            GHC.Classes,
             GHC.Conc,
             GHC.ConsoleHandler,
             GHC.Desugar,