
#11364: Possible type-checker regression in GHC 8.0 -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code fragment works with GHCs prior to GHC 8.0 but not with GHC 8.0: {{{#!hs {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE IncoherentInstances #-} {-# LANGUAGE RankNTypes #-} module Issue where import Data.Coerce (coerce) data Proxy a = Proxy newtype Catch a = Catch a class Throws e type role Throws representational instance Throws (Catch e) newtype Wrap e a = Wrap { unWrap :: Throws e => a } coerceWrap :: Wrap e a -> Wrap (Catch e) a coerceWrap = coerce unthrow :: proxy e -> (Throws e => a) -> a unthrow _ = unWrap . coerceWrap . Wrap {- this works in GHC 7.10.3, but fails in GHC 8.0 with GHCi, version 8.0.0.20160105: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Issue ( Issue.hs, interpreted ) Issue.hs:25:13: error: • Could not deduce (Throws e) from the context: Throws e0 bound by a type expected by the context: Throws e0 => a at Issue.hs:26:13-38 Possible fix: add (Throws e) to the context of the type signature for: unthrow :: proxy e -> (Throws e => a) -> a • In the expression: unWrap . coerceWrap . Wrap In an equation for ‘unthrow’: unthrow _ = unWrap . coerceWrap . Wrap Failed, modules loaded: none. -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11364 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler