
#10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This started out with code that compiled on 7.10, but fails on HEAD (20150711): {{{ {-# LANGUAGE TypeFamilies, StandaloneDeriving, UndecidableInstances #-} module StandaloneDeriving where type family F a newtype D a = D (F a) -- | This works on 7.10.1 and HEAD (20150711) deriving instance Eq (F a) => Eq (D a) -- | This works on 7.10.1, but fails on HEAD (20150711) deriving instance Bounded (F a) => Bounded (D a) }}} which fails on HEAD with: {{{ GHCi, version 7.11.20150711: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling StandaloneDeriving ( StandaloneDeriving.hs, interpreted ) StandaloneDeriving.hs:12:1: error: Couldn't match representation of type ‘a0’ with that of ‘F a’ arising from a use of ‘coerce’ Relevant bindings include minBound :: D a (bound at StandaloneDeriving.hs:12:1) In the expression: coerce (minBound :: F a) :: D a In an equation for ‘minBound’: minBound = coerce (minBound :: F a) :: D a When typechecking the code for ‘minBound’ in a derived instance for ‘Bounded (D a)’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘Bounded (D a)’ StandaloneDeriving.hs:12:1: error: Couldn't match representation of type ‘a1’ with that of ‘F a’ arising from a use of ‘coerce’ Relevant bindings include maxBound :: D a (bound at StandaloneDeriving.hs:12:1) In the expression: coerce (maxBound :: F a) :: D a In an equation for ‘maxBound’: maxBound = coerce (maxBound :: F a) :: D a When typechecking the code for ‘maxBound’ in a derived instance for ‘Bounded (D a)’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘Bounded (D a)’ Failed, modules loaded: none. }}} Which I managed to reduce to: {{{ {-# LANGUAGE TypeFamilies, FlexibleContexts #-} module CoerceFail where import Data.Coerce type family F a newtype D a = D (F a) -- | This works on 7.10.1, but fails on HEAD (20150711) coerceD :: Coercible (F a) (D a) => F a -> D a coerceD = coerce }}} Which also works on 7.10.1 but fails on HEAD with: {{{ GHCi, version 7.11.20150711: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling CoerceFail ( CoerceFail.hs, interpreted ) CoerceFail.hs:12:11: error: Couldn't match representation of type ‘a0’ with that of ‘F a’ arising from a use of ‘coerce’ Relevant bindings include coerceD :: F a -> D a (bound at CoerceFail.hs:12:1) In the expression: coerce In an equation for ‘coerceD’: coerceD = coerce }}} I don't know if this was never supposed to work, and the behaviour on HEAD is correct, or, if this is truly a regression from 7.10 to HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10642 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler