
#15637: Ambiguous type variables in GeneralisedNewtypeDeriving -------------------------------------+------------------------------------- Reporter: i-am-tom | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: Unknown/Multiple GeneralisedNewtypeDeriving, | GeneralizedNewtypeDeriving | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When deriving the `C` instance in the following code: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Test where class C a where f :: String instance C () where f = "foo" newtype T = T () deriving C }}} The following error occurs: {{{ Test.hs:10:27: error: • Ambiguous type variable ‘a0’ arising from a use of ‘f’ prevents the constraint ‘(C a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance C T -- Defined at Test.hs:10:27 instance C () -- Defined at Test.hs:8:10 • In the third argument of ‘GHC.Prim.coerce’, namely ‘f’ In the expression: GHC.Prim.coerce @String @String f :: String In an equation for ‘f’: f = GHC.Prim.coerce @String @String f :: String When typechecking the code for ‘f’ in a derived instance for ‘C T’: To see the code I am typechecking, use -ddump-deriv | 10 | newtype T = T () deriving C | ^ }}} ... and the following core is produced: {{{ ==================== Derived instances ==================== Derived class instances: instance Test.C Test.T where Test.f = GHC.Prim.coerce @GHC.Base.String @GHC.Base.String Test.f :: GHC.Base.String Derived type family instances: }}} The problem seems to be that the `a` should have been set to `()` within the coerced instance. I've been working round this with a `newtype X a = X String` as the result value so that the `a` is present in the signature, but I think this is a bug; should a more specialised instance be generated? I hope this is enough of an explanation! Thanks, Tom -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15637 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler