[commit: packages/base] master: Provide Typeable1..7 as type synonyms (see #8813) (a5383f7)

git at git.haskell.org git at git.haskell.org
Tue Feb 25 10:33:02 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/a5383f7400d05a758094578da28d958fb694b726/base

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

commit a5383f7400d05a758094578da28d958fb694b726
Author: Jose Pedro Magalhaes <jpm at cs.ox.ac.uk>
Date:   Tue Feb 25 10:28:20 2014 +0000

    Provide Typeable1..7 as type synonyms (see #8813)


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

a5383f7400d05a758094578da28d958fb694b726
 Data/Typeable.hs          |    7 +++++++
 Data/Typeable/Internal.hs |   20 +++++++++++++++++++-
 2 files changed, 26 insertions(+), 1 deletion(-)

diff --git a/Data/Typeable.hs b/Data/Typeable.hs
index 2f122b9..4086d05 100644
--- a/Data/Typeable.hs
+++ b/Data/Typeable.hs
@@ -35,6 +35,11 @@
 -- and type-safe cast (but not dynamics) to support the \"Scrap your
 -- boilerplate\" style of generic programming.
 --
+-- Since GHC 7.8, 'Typeable' is poly-kinded. The changes required for this might
+-- break some old programs involving 'Typeable'. More details on this, including
+-- how to fix your code, are on the wiki page:
+-- <https://ghc.haskell.org/trac/ghc/wiki/GhcKinds/PolyTypeable>
+--
 -----------------------------------------------------------------------------
 
 module Data.Typeable
@@ -48,6 +53,8 @@ module Data.Typeable
 
         -- * For backwards compatibility
         typeOf, typeOf1, typeOf2, typeOf3, typeOf4, typeOf5, typeOf6, typeOf7,
+        Typeable1, Typeable2, Typeable3, Typeable4, Typeable5, Typeable6,
+        Typeable7,
 
         -- * Type-safe cast
         cast,
diff --git a/Data/Typeable/Internal.hs b/Data/Typeable/Internal.hs
index a058dc8..cd226f6 100644
--- a/Data/Typeable/Internal.hs
+++ b/Data/Typeable/Internal.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE Unsafe    #-}
+{-# LANGUAGE Unsafe             #-}
+{-# LANGUAGE ConstraintKinds    #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -28,6 +29,7 @@ module Data.Typeable.Internal (
     TypeRep(..),
     Fingerprint(..),
     typeOf, typeOf1, typeOf2, typeOf3, typeOf4, typeOf5, typeOf6, typeOf7,
+    Typeable1, Typeable2, Typeable3, Typeable4, Typeable5, Typeable6, Typeable7,
     TyCon(..),
     typeRep,
     mkTyCon,
@@ -232,6 +234,22 @@ typeOf7 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *)
                 (g :: *). Typeable t => t a b c d e f g -> TypeRep
 typeOf7 _ = typeRep (Proxy :: Proxy t)
 
+type Typeable1 (a :: * -> *)                               = Typeable a
+type Typeable2 (a :: * -> * -> *)                          = Typeable a
+type Typeable3 (a :: * -> * -> * -> *)                     = Typeable a
+type Typeable4 (a :: * -> * -> * -> * -> *)                = Typeable a
+type Typeable5 (a :: * -> * -> * -> * -> * -> *)           = Typeable a
+type Typeable6 (a :: * -> * -> * -> * -> * -> * -> *)      = Typeable a
+type Typeable7 (a :: * -> * -> * -> * -> * -> * -> * -> *) = Typeable a
+
+{-# DEPRECATED Typeable1 "renamed to 'Typeable'" #-} -- deprecated in 7.8
+{-# DEPRECATED Typeable2 "renamed to 'Typeable'" #-} -- deprecated in 7.8
+{-# DEPRECATED Typeable3 "renamed to 'Typeable'" #-} -- deprecated in 7.8
+{-# DEPRECATED Typeable4 "renamed to 'Typeable'" #-} -- deprecated in 7.8
+{-# DEPRECATED Typeable5 "renamed to 'Typeable'" #-} -- deprecated in 7.8
+{-# DEPRECATED Typeable6 "renamed to 'Typeable'" #-} -- deprecated in 7.8
+{-# DEPRECATED Typeable7 "renamed to 'Typeable'" #-} -- deprecated in 7.8
+
 -- | Kind-polymorphic Typeable instance for type application
 instance (Typeable s, Typeable a) => Typeable (s a) where
   typeRep# _ = typeRep# (proxy# :: Proxy# s) `mkAppTy` typeRep# (proxy# :: Proxy# a)



More information about the ghc-commits mailing list