[commit: ghc] ghc-7.10: Add public rnf/hash operations to TypeRep/TyCon (b2b1c8d)

git at git.haskell.org git at git.haskell.org
Sat Mar 7 22:19:05 UTC 2015


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

On branch  : ghc-7.10
Link       : http://ghc.haskell.org/trac/ghc/changeset/b2b1c8d4623db6f8fe38afbe59a8adcf0815056d/ghc

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

commit b2b1c8d4623db6f8fe38afbe59a8adcf0815056d
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu Mar 5 11:56:03 2015 -0600

    Add public rnf/hash operations to TypeRep/TyCon
    
    `TyCon` and `TypeRep` are supposed to be abstract, by providing these
    additional few public operations the need to import
    `Data.Typeable.Internal` is reduced, and future changes to the internal
    structure of `TypeRep`/`TyCon` shouldn't require changes in packages such as
    `deepseq` or `hashable` anymore (hopefully).
    
    (cherry picked from commit 56e0ac98c3a439b8757a2e886db259270bdc85f0)


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

b2b1c8d4623db6f8fe38afbe59a8adcf0815056d
 libraries/base/Data/Typeable.hs          |  4 ++++
 libraries/base/Data/Typeable/Internal.hs | 29 ++++++++++++++++++++++++++++-
 libraries/base/changelog.md              |  3 +++
 3 files changed, 35 insertions(+), 1 deletion(-)

diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index 168600f..7e501a5 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -61,13 +61,17 @@ module Data.Typeable
         
         -- * Type representations
         TypeRep,        -- abstract, instance of: Eq, Show, Typeable
+        typeRepHash,
+        rnfTypeRep,
         showsTypeRep,
 
         TyCon,          -- abstract, instance of: Eq, Show, Typeable
+        tyConHash,
         tyConString,
         tyConPackage,
         tyConModule,
         tyConName,
+        rnfTyCon,
 
         -- * Construction of type representations
         -- mkTyCon,        -- :: String  -> TyCon
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 647697a..8917833 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -42,8 +42,11 @@ module Data.Typeable.Internal (
     splitTyConApp,
     funResultTy,
     typeRepArgs,
+    typeRepHash,
+    rnfTypeRep,
     showsTypeRep,
     tyConString,
+    rnfTyCon,
     listTc, funTc
   ) where
 
@@ -93,7 +96,7 @@ instance Ord TypeRep where
 -- | An abstract representation of a type constructor.  'TyCon' objects can
 -- be built using 'mkTyCon'.
 data TyCon = TyCon {
-   tyConHash    :: {-# UNPACK #-} !Fingerprint,
+   tyConHash    :: {-# UNPACK #-} !Fingerprint, -- ^ @since 4.8.0.0
    tyConPackage :: String, -- ^ @since 4.5.0.0
    tyConModule  :: String, -- ^ @since 4.5.0.0
    tyConName    :: String  -- ^ @since 4.5.0.0
@@ -191,6 +194,12 @@ typeRepArgs (TypeRep _ _ args) = args
 tyConString :: TyCon   -> String
 tyConString = tyConName
 
+-- | Observe the 'Fingerprint' of a type representation
+--
+-- @since 4.8.0.0
+typeRepHash :: TypeRep -> Fingerprint
+typeRepHash (TypeRep fpr _ _) = fpr
+
 -------------------------------------------------------------
 --
 --      The Typeable class and friends
@@ -301,6 +310,24 @@ isTupleTyCon :: TyCon -> Bool
 isTupleTyCon (TyCon _ _ _ ('(':',':_)) = True
 isTupleTyCon _                         = False
 
+-- | Helper to fully evaluate 'TypeRep' for use as @NFData(rnf)@ implementation
+--
+-- @since 4.8.0.0
+rnfTypeRep :: TypeRep -> ()
+rnfTypeRep (TypeRep _ tyc tyrs) = rnfTyCon tyc `seq` go tyrs
+  where
+    go [] = ()
+    go (x:xs) = rnfTypeRep x `seq` go xs
+
+-- | Helper to fully evaluate 'TyCon' for use as @NFData(rnf)@ implementation
+--
+-- @since 4.8.0.0
+rnfTyCon :: TyCon -> ()
+rnfTyCon (TyCon _ tcp tcm tcn) = go tcp `seq` go tcm `seq` go tcn
+  where
+    go [] = ()
+    go (x:xs) = x `seq` go xs
+
 -- Some (Show.TypeRep) helpers:
 
 showArgs :: Show a => ShowS -> [a] -> ShowS
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 89caf01..5635918 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -138,6 +138,9 @@
 
   * Restore invariant in `Data (Ratio a)` instance (#10011)
 
+  * Add/expose `rnfTypeRep`, `rnfTyCon`, `TypeRepHash`, and
+    `TyConHash` helpers to `Data.Typeable`.
+
 ## 4.7.0.2  *Dec 2014*
 
   * Bundled with GHC 7.8.4



More information about the ghc-commits mailing list