[commit: base] data-proxy: Fix problem with deprecating gcast[12] (ebd99ae)
Richard Eisenberg
eir at ghc.haskell.org
Tue Jul 23 16:04:24 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : data-proxy
http://hackage.haskell.org/trac/ghc/changeset/ebd99ae8e9398b764509e64f526db331856ce235
>---------------------------------------------------------------
commit ebd99ae8e9398b764509e64f526db331856ce235
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Mon Jul 22 17:59:31 2013 +0100
Fix problem with deprecating gcast[12]
>---------------------------------------------------------------
Data/Data.hs | 6 +++---
Data/Proxy.hs-boot | 2 +-
Data/Typeable.hs | 22 +++++++---------------
3 files changed, 11 insertions(+), 19 deletions(-)
diff --git a/Data/Data.hs b/Data/Data.hs
index 195dc5c..465b30c 100644
--- a/Data/Data.hs
+++ b/Data/Data.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, RankNTypes, ScopedTypeVariables #-}
+{-# LANGUAGE CPP, RankNTypes, ScopedTypeVariables, PolyKinds #-}
-----------------------------------------------------------------------------
-- |
@@ -265,7 +265,7 @@ class Typeable a => Data a where
-- | Mediate types and unary type constructors.
-- In 'Data' instances of the form @T a@, 'dataCast1' should be defined
- -- as 'gcast1'.
+ -- as 'gcast'.
--
-- The default definition is @'const' 'Nothing'@, which is appropriate
-- for non-unary type constructors.
@@ -276,7 +276,7 @@ class Typeable a => Data a where
-- | Mediate types and binary type constructors.
-- In 'Data' instances of the form @T a b@, 'dataCast2' should be
- -- defined as 'gcast2'.
+ -- defined as 'gcast'.
--
-- The default definition is @'const' 'Nothing'@, which is appropriate
-- for non-binary type constructors.
diff --git a/Data/Proxy.hs-boot b/Data/Proxy.hs-boot
index 99d7dcd..3434d99 100644
--- a/Data/Proxy.hs-boot
+++ b/Data/Proxy.hs-boot
@@ -2,4 +2,4 @@
module Data.Proxy ( Proxy(..) ) where
-data Proxy t = Proxy
\ No newline at end of file
+data Proxy (t :: k) = Proxy
\ No newline at end of file
diff --git a/Data/Typeable.hs b/Data/Typeable.hs
index 84dba1a..34d777c 100644
--- a/Data/Typeable.hs
+++ b/Data/Typeable.hs
@@ -114,23 +114,15 @@ eqT = if typeRep (Proxy :: Proxy a) == typeRep (Proxy :: Proxy b)
-- | A flexible variation parameterised in a type constructor
gcast :: forall a b c. (Typeable a, Typeable b) => c a -> Maybe (c b)
-gcast x = case eqT :: Maybe (a :=: b) of
- Just Refl -> Just x
- Nothing -> Nothing
+gcast x = fmap (\Refl -> x) (eqT :: Maybe (a :=: b))
-{-# DEPRECATED gcast1, gcast2 "Use eqT or poly-kinded gcast instead" #-}
-
--- | Cast for * -> *
-gcast1 :: forall c t t' a. (Typeable (t :: * -> *), Typeable t')
+-- | Cast over @k1 -> k2@
+gcast1 :: forall c t t' a. (Typeable t, Typeable t')
=> c (t a) -> Maybe (c (t' a))
-gcast1 x = if typeRep (Proxy :: Proxy t) == typeRep (Proxy :: Proxy t')
- then Just $ unsafeCoerce x
- else Nothing
+gcast1 x = fmap (\Refl -> x) (eqT :: Maybe (t :=: t'))
--- | Cast for * -> * -> *
-gcast2 :: forall c t t' a b. (Typeable (t :: * -> * -> *), Typeable t')
+-- | Cast over @k1 -> k2 -> k3@
+gcast2 :: forall c t t' a b. (Typeable t, Typeable t')
=> c (t a b) -> Maybe (c (t' a b))
-gcast2 x = if typeRep (Proxy :: Proxy t) == typeRep (Proxy :: Proxy t')
- then Just $ unsafeCoerce x
- else Nothing
+gcast2 x = fmap (\Refl -> x) (eqT :: Maybe (t :=: t'))
More information about the ghc-commits
mailing list