[commit: base] data-proxy: Fix imports (71d53b5)

Richard Eisenberg eir at ghc.haskell.org
Tue Jul 23 16:04:26 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : data-proxy

http://hackage.haskell.org/trac/ghc/changeset/71d53b5aef400c23ac3675ddde3a551bcc6d4cc5

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

commit 71d53b5aef400c23ac3675ddde3a551bcc6d4cc5
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Tue Jul 23 10:41:44 2013 +0100

    Fix imports

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

 Data/Proxy.hs         |    9 ++++++---
 Data/Type/Equality.hs |   13 ++++++++-----
 2 files changed, 14 insertions(+), 8 deletions(-)

diff --git a/Data/Proxy.hs b/Data/Proxy.hs
index 80ad2d5..dc7877a 100644
--- a/Data/Proxy.hs
+++ b/Data/Proxy.hs
@@ -1,13 +1,15 @@
-{-# LANGUAGE PolyKinds, DeriveDataTypeable, NoImplicitPrelude #-}
+{-# LANGUAGE PolyKinds, DeriveDataTypeable, NoImplicitPrelude,
+             DeriveGeneric #-}
 
 module Data.Proxy
   (
-        Proxy(..)
+        Proxy(..), KProxy(..)
   ) where
 
 import Data.Data
 import Data.Monoid
 import Data.Traversable
+import Data.Foldable
 
 import Control.Applicative
 
@@ -16,10 +18,11 @@ import GHC.Show
 import GHC.Read
 import GHC.Enum
 import GHC.Arr
+import qualified GHC.Generics as Generics
 
 -- | A concrete, poly-kinded proxy type
 data Proxy t = Proxy
-  deriving (Typeable, Generic, Generic1)
+  deriving (Typeable, Generics.Generic)
 
 -- | A concrete, promotable proxy type, for use at the kind level
 -- There are no instances for this because it is intended at the kind level only
diff --git a/Data/Type/Equality.hs b/Data/Type/Equality.hs
index 8e55b9a..343d0eb 100644
--- a/Data/Type/Equality.hs
+++ b/Data/Type/Equality.hs
@@ -6,13 +6,16 @@
 {-# LANGUAGE FlexibleInstances  #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE NoImplicitPrelude  #-}
+{-# LANGUAGE PolyKinds          #-}
 
 module Data.Type.Equality where
 
 import Data.Data
-import Data.Ix
-import GHC.Generics
-import Control.Exception
+import Data.Maybe
+import GHC.Enum
+import GHC.Show
+import GHC.Read
+import GHC.Base
 import Control.Category
 
 infix 4 :=:
@@ -38,7 +41,7 @@ trans Refl Refl = Refl
 
 -- | Type-safe cast, using propositional equality
 coerce :: (a :=: b) -> a -> b
-coerce Refl = Prelude.id
+coerce Refl x = x
 
 -- | Lift equality into a unary type constructor
 liftEq :: (a :=: b) -> (f a :=: f b)
@@ -68,7 +71,7 @@ deriving instance Typeable (:=:)
 deriving instance (Typeable a, Data a) => Data (a :=: a)
 
 instance Read (a :=: a) where
-  readsPrec d = readParen False (\r -> [(Refl, s) | ("Refl",s) <- lex r ])
+  readsPrec d = readParen (d > 10) (\r -> [(Refl, s) | ("Refl",s) <- lex r ])
 
 instance Category (:=:) where
   id          = Refl






More information about the ghc-commits mailing list