[commit: packages/base] master: Define typeRep in terms of new Proxy# (7bd64c5)

git at git.haskell.org git at git.haskell.org
Fri Sep 27 07:19:36 CEST 2013


Repository : ssh://git@git.haskell.org/base

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/7bd64c53659e3378b363adad2ce2525a08d88a26/base

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

commit 7bd64c53659e3378b363adad2ce2525a08d88a26
Author: Austin Seipp <austin at well-typed.com>
Date:   Thu Sep 26 01:43:54 2013 -0500

    Define typeRep in terms of new Proxy#
    
    Data.Typeable.Internal.Typeable now contains typeRep# - defined over
    Proxy# - instead of typeRep, the latter now being a wrapper of the
    former.
    
    Authored-by: Edward Kmett <ekmett at gmail.com>
    Authored-by: Austin Seipp <austin at well-typed.com>
    Signed-off-by: Austin Seipp <austin at well-typed.com>


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

7bd64c53659e3378b363adad2ce2525a08d88a26
 Data/Typeable.hs          |    4 +++-
 Data/Typeable/Internal.hs |   18 +++++++++++-------
 2 files changed, 14 insertions(+), 8 deletions(-)

diff --git a/Data/Typeable.hs b/Data/Typeable.hs
index 355f17b..bacb426 100644
--- a/Data/Typeable.hs
+++ b/Data/Typeable.hs
@@ -7,6 +7,7 @@
            , TypeOperators
            , PolyKinds
            , GADTs
+           , MagicHash
   #-}
 {-# OPTIONS_GHC -funbox-strict-fields #-}
 
@@ -43,7 +44,8 @@ module Data.Typeable
         Proxy (..),
 
         -- * The Typeable class
-        Typeable( typeRep ),
+        Typeable,
+        typeRep,
 
         -- * Propositional equality
         (:=:)(Refl),
diff --git a/Data/Typeable/Internal.hs b/Data/Typeable/Internal.hs
index 447b069..517b9a8 100644
--- a/Data/Typeable/Internal.hs
+++ b/Data/Typeable/Internal.hs
@@ -29,6 +29,7 @@ module Data.Typeable.Internal (
     Fingerprint(..),
     typeOf, typeOf1, typeOf2, typeOf3, typeOf4, typeOf5, typeOf6, typeOf7,
     TyCon(..),
+    typeRep,
     mkTyCon,
     mkTyCon3,
     mkTyConApp,
@@ -190,11 +191,15 @@ tyConString = tyConName
 -- | The class 'Typeable' allows a concrete representation of a type to
 -- be calculated.
 class Typeable a where
-  typeRep :: proxy a -> TypeRep
-  -- ^ Takes a value of type @a@ and returns a concrete representation
-  -- of that type.
-  --
-  -- /Version: 4.7.0.0/
+  typeRep# :: Proxy# a -> TypeRep
+
+--  Takes a value of type @a@ and returns a concrete representation
+-- of that type.
+--
+-- /Version: 4.7.0.0/
+typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep
+typeRep _ = typeRep# (proxy# :: Proxy# a)
+{-# INLINE typeRep #-}
 
 -- Keeping backwards-compatibility
 typeOf :: forall a. Typeable a => a -> TypeRep
@@ -228,8 +233,7 @@ typeOf7 _ = typeRep (Proxy :: Proxy t)
 
 -- | Kind-polymorphic Typeable instance for type application
 instance (Typeable s, Typeable a) => Typeable (s a) where
-  typeRep _ = typeRep (Proxy :: Proxy s) `mkAppTy` typeRep (Proxy :: Proxy a)
-
+  typeRep# _ = typeRep# (proxy# :: Proxy# s) `mkAppTy` typeRep# (proxy# :: Proxy# a)
 
 ----------------- Showing TypeReps --------------------
 




More information about the ghc-commits mailing list