Repository : ssh://darcs.haskell.org//srv/darcs/packages/ghc-prim

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/cd4ca89b608d1a9000700ec5bdb1524677386c5d

>---------------------------------------------------------------

commit cd4ca89b608d1a9000700ec5bdb1524677386c5d
Author: Ian Lynagh <[email protected]>
Date:   Fri Aug 26 21:37:59 2011 +0100

    Merge GHC.Unit into GHC.Tuple, and GHC.Ordering into GHC.Types

>---------------------------------------------------------------

 GHC/Classes.hs  |    2 --
 GHC/Debug.hs    |    2 +-
 GHC/Ordering.hs |   13 -------------
 GHC/Tuple.hs    |    4 ++++
 GHC/Types.hs    |    6 +++++-
 GHC/Unit.hs     |   19 -------------------
 ghc-prim.cabal  |    2 --
 7 files changed, 10 insertions(+), 38 deletions(-)

diff --git a/GHC/Classes.hs b/GHC/Classes.hs
index fabf0eb..7be590b 100644
--- a/GHC/Classes.hs
+++ b/GHC/Classes.hs
@@ -22,11 +22,9 @@ module GHC.Classes where
 
 -- GHC.Magic is used in some derived instances
 import GHC.Magic ()
-import GHC.Ordering
 import GHC.Prim
 import GHC.Tuple
 import GHC.Types
-import GHC.Unit
 -- For defining instances for the generic deriving mechanism
 import GHC.Generics (Arity(..), Associativity(..), Fixity(..))
 
diff --git a/GHC/Debug.hs b/GHC/Debug.hs
index e42ca5f..63b1d84 100644
--- a/GHC/Debug.hs
+++ b/GHC/Debug.hs
@@ -4,7 +4,7 @@ module GHC.Debug ( debugLn, debugErrLn ) where
 
 import GHC.Prim
 import GHC.Types
-import GHC.Unit ()
+import GHC.Tuple ()
 
 debugLn :: [Char] -> IO ()
 debugLn xs = IO (\s0 ->
diff --git a/GHC/Ordering.hs b/GHC/Ordering.hs
deleted file mode 100644
index 8ad3f62..0000000
--- a/GHC/Ordering.hs
+++ /dev/null
@@ -1,13 +0,0 @@
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude, DeriveGeneric #-}
-
-module GHC.Ordering where
-
-import GHC.Generics (Generic)
-
-
-default ()
-
-data Ordering = LT | EQ | GT
-        deriving Generic
-
diff --git a/GHC/Tuple.hs b/GHC/Tuple.hs
index f03de3d..b1573c2 100644
--- a/GHC/Tuple.hs
+++ b/GHC/Tuple.hs
@@ -21,6 +21,10 @@ import GHC.Generics (Generic)
 
 default () -- Double and Integer aren't available yet
 
+-- | The unit datatype @()@ has one non-undefined member, the nullary
+-- constructor @()@.
+data () = () deriving Generic
+
 data (,) a b = (,) a b
     deriving Generic
 data (,,) a b c = (,,) a b c
diff --git a/GHC/Types.hs b/GHC/Types.hs
index 005a588..3303cda 100644
--- a/GHC/Types.hs
+++ b/GHC/Types.hs
@@ -17,7 +17,8 @@
 
 module GHC.Types (
         Bool(..), Char(..), Int(..),
-        Float(..), Double(..), IO(..)
+        Float(..), Double(..),
+        Ordering(..), IO(..)
     ) where
 
 import GHC.Prim
@@ -58,6 +59,9 @@ data Float = F# Float#
 -- to the IEEE double-precision type.
 data Double = D# Double#
 
+data Ordering = LT | EQ | GT
+        deriving Generic
+
 {- |
 A value of type @'IO' a@ is a computation which, when performed,
 does some I\/O before returning a value of type @a@.
diff --git a/GHC/Unit.hs b/GHC/Unit.hs
deleted file mode 100644
index a65fe18..0000000
--- a/GHC/Unit.hs
+++ /dev/null
@@ -1,19 +0,0 @@
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude, DeriveGeneric #-}
-
-module GHC.Unit where
-
-import GHC.Generics (Generic)
-
-
-default ()
-
-{-
-The Unit type is here because GHC.PrimopWrappers needs to use it in a
-type signature.
--}
-
--- | The unit datatype @()@ has one non-undefined member, the nullary
--- constructor @()@.
-data () = () deriving Generic
-
diff --git a/ghc-prim.cabal b/ghc-prim.cabal
index c7a19a7..9a89526 100644
--- a/ghc-prim.cabal
+++ b/ghc-prim.cabal
@@ -27,12 +27,10 @@ Library {
         GHC.Debug
         GHC.Generics
         GHC.Magic
-        GHC.Ordering
         GHC.PrimopWrappers
         GHC.IntWord64
         GHC.Tuple
         GHC.Types
-        GHC.Unit
 
     if flag(include-ghc-prim) {
         exposed-modules: GHC.Prim



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to