[commit: ghc] master: Remove the deprecated Typeable{1..7} type synonyms (a81b5b0)

git at git.haskell.org git at git.haskell.org
Sat Aug 5 16:12:53 UTC 2017


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

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

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

commit a81b5b0067b6530f5883aeb0154a407a54d14c62
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Sat Aug 5 12:02:41 2017 -0400

    Remove the deprecated Typeable{1..7} type synonyms
    
    Summary:
    `Typeable{1..7}` (type synonyms for the poly-kinded `Typeable`) have
    been deprecated since GHC 7.8. They're now causing problems for users who try
    to still work with them in legacy code, since they can no longer be used in
    instances. To avoid this sort of confusion, let's just remove `Typeable{1..7}`
    altogether. Resolves #14047.
    
    Reviewers: bgamari, austin, hvr
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie
    
    GHC Trac Issues: #14047
    
    Differential Revision: https://phabricator.haskell.org/D3817


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

a81b5b0067b6530f5883aeb0154a407a54d14c62
 libraries/base/Data/Typeable.hs              | 18 ------------------
 libraries/base/changelog.md                  |  2 ++
 testsuite/tests/deriving/should_run/T3087.hs |  2 +-
 3 files changed, 3 insertions(+), 19 deletions(-)

diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index 6157e82..61b70cf 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -86,8 +86,6 @@ module Data.Typeable
 
       -- * For backwards compatibility
     , typeOf1, typeOf2, typeOf3, typeOf4, typeOf5, typeOf6, typeOf7
-    , Typeable1, Typeable2, Typeable3, Typeable4
-    , Typeable5, Typeable6, Typeable7
     ) where
 
 import qualified Data.Typeable.Internal as I
@@ -225,19 +223,3 @@ 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.someTypeRep (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
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index a9f2992..708676f 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -12,6 +12,8 @@
 
   * Add `<&>` operator to `Data.Functor` (#14029)
 
+  * Remove the deprecated `Typeable{1..7}` type synonyms (#14047)
+
 ## 4.10.0.0 *April 2017*
   * Bundled with GHC *TBA*
 
diff --git a/testsuite/tests/deriving/should_run/T3087.hs b/testsuite/tests/deriving/should_run/T3087.hs
index 9d3be07..1e20b9e 100644
--- a/testsuite/tests/deriving/should_run/T3087.hs
+++ b/testsuite/tests/deriving/should_run/T3087.hs
@@ -14,7 +14,7 @@ test1' = undefined `ext1Q` (\ (MyJust _) -> ()) $ MyJust ()
 
 newtype Q r a = Q { unQ :: a -> r }
 
-ext2Q :: (Data d, Typeable2 t)
+ext2Q :: (Data d, Typeable t)
       => (d -> q) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> q)
       -> d -> q
 ext2Q def ext arg =



More information about the ghc-commits mailing list