
#10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by inaki: Old description:
In upgrading to7.10, code of the form {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible)
data X a
doCoerce :: Coercible a (X a) => a -> X a doCoerce = coerce }}} fails to compile in 7.10.1 and 7.10.2 with the error {{{ testCoerce.hs:6:13: Could not deduce (a ~ X a) from the context (Coercible a (X a)) bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13-41 ‘a’ is a rigid type variable bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13 Relevant role signatures: type role X phantom In the ambiguity check for the type signature for ‘doCoerce’: doCoerce :: forall a. Coercible a (X a) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘doCoerce’: doCoerce :: Coercible a (X a) => a -> X a }}} while it works in 7.8.4.
Surprisingly (to me at least), the code works in 7.10.1 and 7.10.2 if I change it to {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible)
data X a
doCoerce :: Coercible a (X b) => a -> X a doCoerce = coerce }}} while it fails to compile in 7.8.4 with the error {{{ testCoerce.hs:6:13: Could not coerce from ‘a’ to ‘X b0’ because ‘a’ and ‘X b0’ are different types. arising from the ambiguity check for ‘doCoerce’ from the context (Coercible a (X b)) bound by the type signature for doCoerce :: Coercible a (X b) => a -> X a at testCoerce.hs:6:13-41 The type variable ‘b0’ is ambiguous In the ambiguity check for: forall a b. Coercible a (X b) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘doCoerce’: doCoerce :: Coercible a (X b) => a -> X a }}}
The coercion pattern may look a bit funny, but it is rather useful when one has newtypes of the form {{{#!hs newtype Y = Y (ForeignPtr Y) }}} which appear naturally when writing bindings to C libraries, and one wants to get access to the underlying ForeignPtr from Y (here X -> ForeignPtr). The relevant Coercible instance here is Coercible Y (ForeignPtr Y), as above.
I would have expected the version with context "Coercible a (X a)" to be accepted, as 7.8.4 does, since it seems to be a specialization of the more general coerce, but maybe I am missing something?
New description: In upgrading to7.10, code of the form {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible) data X a doCoerce :: Coercible a (X a) => a -> X a doCoerce = coerce }}} fails to compile in 7.10.1 and 7.10.2 with the error {{{ testCoerce.hs:6:13: Could not deduce (a ~ X a) from the context (Coercible a (X a)) bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13-41 ‘a’ is a rigid type variable bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13 Relevant role signatures: type role X phantom In the ambiguity check for the type signature for ‘doCoerce’: doCoerce :: forall a. Coercible a (X a) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘doCoerce’: doCoerce :: Coercible a (X a) => a -> X a }}} while it works in 7.8.4. Surprisingly (to me at least), the code works in 7.10.1 and 7.10.2 if I change it to {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible) data X a doCoerce :: Coercible a (X b) => a -> X a doCoerce = coerce }}} while it fails to compile in 7.8.4 with the error {{{ testCoerce.hs:6:13: Could not coerce from ‘a’ to ‘X b0’ because ‘a’ and ‘X b0’ are different types. arising from the ambiguity check for ‘doCoerce’ from the context (Coercible a (X b)) bound by the type signature for doCoerce :: Coercible a (X b) => a -> X a at testCoerce.hs:6:13-41 The type variable ‘b0’ is ambiguous In the ambiguity check for: forall a b. Coercible a (X b) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ‘doCoerce’: doCoerce :: Coercible a (X b) => a -> X a }}} The coercion pattern may look a bit funny, but it is rather useful when one has newtypes of the form {{{#!hs newtype Y = Y (ForeignPtr Y) }}} which appear naturally when writing bindings to C libraries, and one wants to get access to the underlying ForeignPtr from Y (here X is ForeignPtr). The relevant Coercible instance here is Coercible Y (ForeignPtr Y), as above. I would have expected the version with context "Coercible a (X a)" to be accepted, as 7.8.4 does, since it seems to be a specialization of the more general coerce, but maybe I am missing something? -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10715#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler