[commit: ghc] master: Data.Typeable: Export splitTyConApp, typeRepArgs, and typeRepTyCon (6b15dfe)

git at git.haskell.org git at git.haskell.org
Thu Mar 9 22:53:03 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/6b15dfe85052c40f0cedf9bdbb0c9943a4977492/ghc

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

commit 6b15dfe85052c40f0cedf9bdbb0c9943a4977492
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Thu Mar 9 16:20:38 2017 -0500

    Data.Typeable: Export splitTyConApp, typeRepArgs, and typeRepTyCon
    
    Test Plan: Validate
    
    Reviewers: austin, hvr, RyanGlScott
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3294


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

6b15dfe85052c40f0cedf9bdbb0c9943a4977492
 libraries/base/Data/Typeable.hs          | 26 ++++++++++++++++++--------
 libraries/base/Data/Typeable/Internal.hs |  2 ++
 libraries/base/Type/Reflection.hs        |  2 ++
 libraries/base/Type/Reflection/Unsafe.hs | 17 ++++++++++-------
 libraries/base/changelog.md              |  7 +++++++
 5 files changed, 39 insertions(+), 15 deletions(-)

diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index 8a6422e..d4b28f1 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -65,13 +65,15 @@ module Data.Typeable
 
       -- * Type representations
     , TypeRep
-    , typeRepTyCon
     , rnfTypeRep
     , showsTypeRep
     , mkFunTy
 
       -- * Observing type representations
     , funResultTy
+    , splitTyConApp
+    , typeRepArgs
+    , typeRepTyCon
     , I.typeRepFingerprint
 
       -- * Type constructors
@@ -81,6 +83,7 @@ module Data.Typeable
     , I.tyConModule
     , I.tyConName
     , I.rnfTyCon
+    , I.tyConFingerprint
 
       -- * For backwards compatibility
     , typeOf1, typeOf2, typeOf3, typeOf4, typeOf5, typeOf6, typeOf7
@@ -149,10 +152,6 @@ gcast2 :: forall c t t' a b. (Typeable t, Typeable t')
        => c (t a b) -> Maybe (c (t' a b))
 gcast2 x = fmap (\Refl -> x) (eqT :: Maybe (t :~: t'))
 
--- | Observe the type constructor of a quantified type representation.
-typeRepTyCon :: TypeRep -> TyCon
-typeRepTyCon = I.typeRepXTyCon
-
 -- | Applies a type to a function type. Returns: @Just u@ if the first argument
 -- represents a function of type @t -> u@ and the second argument represents a
 -- function of type @t at . Otherwise, returns @Nothing at .
@@ -173,9 +172,20 @@ mkFunTy (I.SomeTypeRep arg) (I.SomeTypeRep res)
   | otherwise
   = error $ "mkFunTy: Attempted to construct function type from non-lifted "++
             "type: arg="++show arg++", res="++show res
-  where liftedTy = I.typeRep :: I.TypeRep *
-  -- TODO: We should be able to support this but the kind of (->) must be
-  -- generalized
+  where liftedTy = I.typeRep :: I.TypeRep Type
+
+-- | Splits a type constructor application. Note that if the type constructor is
+-- polymorphic, this will not return the kinds that were used.
+splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
+splitTyConApp (I.SomeTypeRep x) = I.splitApps x
+
+-- | Observe the argument types of a type representation
+typeRepArgs :: TypeRep -> [TypeRep]
+typeRepArgs ty = case splitTyConApp ty of (_, args) -> args
+
+-- | Observe the type constructor of a quantified type representation.
+typeRepTyCon :: TypeRep -> TyCon
+typeRepTyCon = I.typeRepXTyCon
 
 -- | Force a 'TypeRep' to normal form.
 rnfTypeRep :: TypeRep -> ()
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 85a356c..f4e690b 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -45,6 +45,7 @@ module Data.Typeable.Internal (
     -- * TyCon
     TyCon,   -- Abstract
     tyConPackage, tyConModule, tyConName, tyConKindArgs, tyConKindRep,
+    tyConFingerprint,
     KindRep(.., KindRepTypeLit), TypeLitSort(..),
     rnfTyCon,
 
@@ -58,6 +59,7 @@ module Data.Typeable.Internal (
     rnfTypeRep,
     eqTypeRep,
     typeRepKind,
+    splitApps,
 
     -- * SomeTypeRep
     SomeTypeRep(..),
diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs
index 59f16ac..dc1c3cf 100644
--- a/libraries/base/Type/Reflection.hs
+++ b/libraries/base/Type/Reflection.hs
@@ -45,6 +45,7 @@ module Type.Reflection
     , I.rnfTypeRep
     , I.eqTypeRep
     , I.typeRepKind
+    , I.splitApps
 
       -- ** Quantified
       --
@@ -61,6 +62,7 @@ module Type.Reflection
     , I.tyConModule
     , I.tyConName
     , I.rnfTyCon
+    , I.tyConFingerprint
 
       -- * Module names
     , I.Module
diff --git a/libraries/base/Type/Reflection/Unsafe.hs b/libraries/base/Type/Reflection/Unsafe.hs
index 4e367f5..4cffd89 100644
--- a/libraries/base/Type/Reflection/Unsafe.hs
+++ b/libraries/base/Type/Reflection/Unsafe.hs
@@ -4,19 +4,22 @@
 -- Copyright   :  (c) The University of Glasgow, CWI 2001--2015
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
 --
--- The representations of the types TyCon and TypeRep, and the
--- function mkTyCon which is used by derived instances of Typeable to
--- construct a TyCon.
+-- The representations of the types 'TyCon' and 'TypeRep', and the function
+-- 'mkTyCon' which is used by derived instances of 'Typeable' to construct
+-- 'TyCon's.
 --
--- Be warned, these functions can be used to construct ill-typed
+-- Be warned, these functions can be used to construct ill-kinded
 -- type representations.
 --
 -----------------------------------------------------------------------------
 
 module Type.Reflection.Unsafe (
-    tyConKindRep, tyConKindArgs,
-    KindRep(..), TypeLitSort(..),
-    mkTrCon, mkTrApp, mkTyCon
+      -- * Type representations
+      TypeRep, mkTrApp, mkTyCon
+      -- * Kind representations
+    , KindRep(..), TypeLitSort(..)
+      -- * Type constructors
+    , TyCon, mkTrCon, tyConKindRep, tyConKindArgs,
   ) where
 
 import Data.Typeable.Internal
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 2c9d029..abae5ae 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -77,6 +77,13 @@
     `Data.Foldable` to use `foldl1` instead of `foldr1`. This makes them run
     in constant space when applied to lists. (#10830)
 
+  * `mkFunTy`, `mkAppTy`, and `mkTyConApp` from `Data.Typeable` no longer exist.
+    This functionality is superceded by the interfaces provided by
+    `Data.Reflection`.
+
+  * `mkTyCon3` is no longer exported by `Data.Typeable`. This function is
+    replaced by `Type.Reflection.Unsafe.mkTyCon`.
+
 ## 4.9.0.0  *May 2016*
 
   * Bundled with GHC 8.0



More information about the ghc-commits mailing list