[commit: ghc] master: Typeable: Fix remaining typeRepX referencds (a3e4f69)
git at git.haskell.org
git at git.haskell.org
Mon Mar 13 21:06:52 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/a3e4f693e231ce85587865e0383e0403cd897a60/ghc
>---------------------------------------------------------------
commit a3e4f693e231ce85587865e0383e0403cd897a60
Author: Ben Gamari <ben at smart-cactus.org>
Date: Mon Mar 13 15:20:40 2017 -0400
Typeable: Fix remaining typeRepX referencds
What was previously known as TypeRepX is now known as SomeTypeRep.
>---------------------------------------------------------------
a3e4f693e231ce85587865e0383e0403cd897a60
libraries/base/Data/Typeable.hs | 22 +++++++++++-----------
libraries/base/Data/Typeable/Internal.hs | 20 ++++++++++----------
libraries/base/Type/Reflection.hs | 6 +++---
3 files changed, 24 insertions(+), 24 deletions(-)
diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index 33bbf86..4268619 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -105,14 +105,14 @@ type TypeRep = I.SomeTypeRep
-- | Observe a type representation for the type of a value.
typeOf :: forall a. Typeable a => a -> TypeRep
-typeOf _ = I.typeRepX (Proxy :: Proxy a)
+typeOf _ = I.someTypeRep (Proxy :: Proxy a)
-- | Takes a value of type @a@ and returns a concrete representation
-- of that type.
--
-- @since 4.7.0.0
typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep
-typeRep = I.typeRepX
+typeRep = I.someTypeRep
-- | Show a type representation
showsTypeRep :: TypeRep -> ShowS
@@ -185,14 +185,14 @@ typeRepArgs ty = case splitTyConApp ty of (_, args) -> args
-- | Observe the type constructor of a quantified type representation.
typeRepTyCon :: TypeRep -> TyCon
-typeRepTyCon = I.typeRepXTyCon
+typeRepTyCon = I.someTypeRepTyCon
-- | 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
+typeRepFingerprint = I.someTypeRepFingerprint
-- | Force a 'TypeRep' to normal form.
rnfTypeRep :: TypeRep -> ()
@@ -201,30 +201,30 @@ rnfTypeRep = I.rnfSomeTypeRep
-- Keeping backwards-compatibility
typeOf1 :: forall t (a :: *). Typeable t => t a -> TypeRep
-typeOf1 _ = I.typeRepX (Proxy :: Proxy t)
+typeOf1 _ = I.someTypeRep (Proxy :: Proxy t)
typeOf2 :: forall t (a :: *) (b :: *). Typeable t => t a b -> TypeRep
-typeOf2 _ = I.typeRepX (Proxy :: Proxy t)
+typeOf2 _ = I.someTypeRep (Proxy :: Proxy t)
typeOf3 :: forall t (a :: *) (b :: *) (c :: *). Typeable t
=> t a b c -> TypeRep
-typeOf3 _ = I.typeRepX (Proxy :: Proxy t)
+typeOf3 _ = I.someTypeRep (Proxy :: Proxy t)
typeOf4 :: forall t (a :: *) (b :: *) (c :: *) (d :: *). Typeable t
=> t a b c d -> TypeRep
-typeOf4 _ = I.typeRepX (Proxy :: Proxy t)
+typeOf4 _ = I.someTypeRep (Proxy :: Proxy t)
typeOf5 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *). Typeable t
=> t a b c d e -> TypeRep
-typeOf5 _ = I.typeRepX (Proxy :: Proxy t)
+typeOf5 _ = I.someTypeRep (Proxy :: Proxy t)
typeOf6 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *).
Typeable t => t a b c d e f -> TypeRep
-typeOf6 _ = I.typeRepX (Proxy :: Proxy t)
+typeOf6 _ = I.someTypeRep (Proxy :: Proxy t)
typeOf7 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *)
(g :: *). Typeable t => t a b c d e f g -> TypeRep
-typeOf7 _ = I.typeRepX (Proxy :: Proxy t)
+typeOf7 _ = I.someTypeRep (Proxy :: Proxy t)
type Typeable1 (a :: * -> *) = Typeable a
type Typeable2 (a :: * -> * -> *) = Typeable a
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index f4e690b..48da8dd 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -63,9 +63,9 @@ module Data.Typeable.Internal (
-- * SomeTypeRep
SomeTypeRep(..),
- typeRepX,
- typeRepXTyCon,
- typeRepXFingerprint,
+ someTypeRep,
+ someTypeRepTyCon,
+ someTypeRepFingerprint,
rnfSomeTypeRep,
-- * Construction
@@ -250,7 +250,7 @@ mkTrCon :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a
mkTrCon tc kind_vars = TrTyCon fpr tc kind_vars
where
fpr_tc = tyConFingerprint tc
- fpr_kvs = map typeRepXFingerprint kind_vars
+ fpr_kvs = map someTypeRepFingerprint kind_vars
fpr = fingerprintFingerprints (fpr_tc:fpr_kvs)
-- | Construct a representation for a type application.
@@ -298,8 +298,8 @@ pattern Con' con ks <- TrTyCon _ con ks
----------------- Observation ---------------------
-- | Observe the type constructor of a quantified type representation.
-typeRepXTyCon :: SomeTypeRep -> TyCon
-typeRepXTyCon (SomeTypeRep t) = typeRepTyCon t
+someTypeRepTyCon :: SomeTypeRep -> TyCon
+someTypeRepTyCon (SomeTypeRep t) = typeRepTyCon t
-- | Observe the type constructor of a type representation
typeRepTyCon :: TypeRep a -> TyCon
@@ -470,12 +470,12 @@ typeOf _ = typeRep
-- of that type.
--
-- @since 4.7.0.0
-typeRepX :: forall proxy a. Typeable a => proxy a -> SomeTypeRep
-typeRepX _ = SomeTypeRep (typeRep :: TypeRep a)
+someTypeRep :: forall proxy a. Typeable a => proxy a -> SomeTypeRep
+someTypeRep _ = SomeTypeRep (typeRep :: TypeRep a)
{-# INLINE typeRep #-}
-typeRepXFingerprint :: SomeTypeRep -> Fingerprint
-typeRepXFingerprint (SomeTypeRep t) = typeRepFingerprint t
+someTypeRepFingerprint :: SomeTypeRep -> Fingerprint
+someTypeRepFingerprint (SomeTypeRep t) = typeRepFingerprint t
----------------- Showing TypeReps --------------------
diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs
index 232ae2c..cb0337a 100644
--- a/libraries/base/Type/Reflection.hs
+++ b/libraries/base/Type/Reflection.hs
@@ -52,9 +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.someTypeRep
+ , I.someTypeRepTyCon
+ , I.someTypeRepFingerprint
, I.rnfSomeTypeRep
-- * Type constructors
More information about the ghc-commits
mailing list