[commit: ghc] master: Make exports from Data.Typeable and Type.Reflection consistent (11ea370)

git at git.haskell.org git at git.haskell.org
Mon Mar 13 21:06:49 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/11ea370107c5b354918ff885c582299fadfe5ea9/ghc

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

commit 11ea370107c5b354918ff885c582299fadfe5ea9
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Mon Mar 13 15:19:03 2017 -0400

    Make exports from Data.Typeable and Type.Reflection consistent
    
    This fixes some idiosyncracies I noticed between `Data.Typeable` and
    `Type.Reflection`:
    
    * `showsTypeRep` (from `Data.Typeable`) had the type `SomeTypeRep ->
      ShowS`, despite the fact that `SomeTypeRep` isn't exported from
      `Data.Typeable`. I changed it to be `Data.Typeable.TypeRep -> ShowS`.
    
    * Similarly, `typeRepFingerprint` (reexported from `Data.Typeable`) had
      the type `SomeTypeRep -> Fingerprint`. I changed it to `Data.Typeable.TypeRep
      -> Fingerprint`.
    
    * `Type.Reflection` wasn't exporting `typeRepX` or `typeRepXFingerprint`,
      despite the fact that their counterparts were exported from `Data.Typeable`.
      `Type.Reflection` now exports them as well.
    
    * `withTypeable :: TypeRep (a :: k) -> (Typeable a => r) -> r` was being
       reexported from `Data.Typeable`. This is in spite of the fact that you
       can't actually use the type-indexed `TypeRep a` by importing
       `Data.Typeable` alone. I decided to remove this export from `Data.Typeable`.
    
    Reviewers: bgamari, austin, hvr
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3309


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

11ea370107c5b354918ff885c582299fadfe5ea9
 libraries/base/Data/Typeable.hs   | 13 ++++++++++---
 libraries/base/Type/Reflection.hs |  2 ++
 2 files changed, 12 insertions(+), 3 deletions(-)

diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index d4b28f1..33bbf86 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -45,7 +45,6 @@ module Data.Typeable
       Typeable
     , typeOf
     , typeRep
-    , I.withTypeable
 
       -- * Propositional equality
     , (:~:)(Refl)
@@ -74,7 +73,7 @@ module Data.Typeable
     , splitTyConApp
     , typeRepArgs
     , typeRepTyCon
-    , I.typeRepFingerprint
+    , typeRepFingerprint
 
       -- * Type constructors
     , I.TyCon          -- abstract, instance of: Eq, Show, Typeable
@@ -97,6 +96,7 @@ import Data.Type.Equality
 
 import Data.Maybe
 import Data.Proxy
+import GHC.Fingerprint.Type
 import GHC.Show
 import GHC.Base
 
@@ -115,7 +115,7 @@ typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep
 typeRep = I.typeRepX
 
 -- | Show a type representation
-showsTypeRep :: I.SomeTypeRep -> ShowS
+showsTypeRep :: TypeRep -> ShowS
 showsTypeRep = shows
 
 -- | The type-safe cast operation
@@ -187,6 +187,13 @@ typeRepArgs ty = case splitTyConApp ty of (_, args) -> args
 typeRepTyCon :: TypeRep -> TyCon
 typeRepTyCon = I.typeRepXTyCon
 
+-- | Takes a value of type @a@ and returns a concrete representation
+-- of that type.
+--
+-- @since 4.7.0.0
+typeRepFingerprint :: TypeRep -> Fingerprint
+typeRepFingerprint = I.typeRepXFingerprint
+
 -- | Force a 'TypeRep' to normal form.
 rnfTypeRep :: TypeRep -> ()
 rnfTypeRep = I.rnfSomeTypeRep
diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs
index dc1c3cf..232ae2c 100644
--- a/libraries/base/Type/Reflection.hs
+++ b/libraries/base/Type/Reflection.hs
@@ -52,7 +52,9 @@ module Type.Reflection
       -- "Data.Typeable" exports a variant of this interface (named differently
       -- for backwards compatibility).
     , I.SomeTypeRep(..)
+    , I.typeRepX
     , I.typeRepXTyCon
+    , I.typeRepXFingerprint
     , I.rnfSomeTypeRep
 
       -- * Type constructors



More information about the ghc-commits mailing list