[GHC] #12098: Typechecker regression in 8.0.1

#12098: Typechecker regression in 8.0.1 -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Windows Architecture: x86 | Type of failure: GHC rejects | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code: {{{#!hs {-# LANGUAGE IncoherentInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RoleAnnotations #-} module Bug where import Data.Proxy (Proxy(..)) import GHC.Prim (coerce) class Throws e where {} type role Throws representational newtype Wrap e a = Wrap { unWrap :: Throws e => a } coerceWrap :: Wrap e a -> Wrap (Catch e) a coerceWrap = coerce newtype Catch a = Catch a instance Throws (Catch e) where {} unthrow :: Proxy e -> (Throws e => a) -> a unthrow _ = unWrap . coerceWrap . Wrap }}} compiles fine with ghc 7.10.2 but fails with ghc 8.0.1 with error: {{{ Bug.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 Bug.hs:25: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 }}} This code is extracted from blog post http://www.well- typed.com/blog/2015/07/checked-exceptions/ and gist https://gist.github.com/edsko/f1f566f77422398fba7d -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12098 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12098: Typechecker regression in 8.0.1 -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11364 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #11364 * priority: highest => normal * architecture: x86 => Unknown/Multiple * os: Windows => Unknown/Multiple Comment: Duplicate of #11364. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12098#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC