Skip to content
Snippets Groups Projects
Commit a81b5b00 authored by Ryan Scott's avatar Ryan Scott
Browse files

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
parent 394c391a
No related branches found
No related tags found
No related merge requests found
......@@ -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
......@@ -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*
......
......@@ -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 =
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment