[GHC] #15637: Ambiguous type variables in GeneralisedNewtypeDeriving

#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

#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 Resolution: | Keywords: | GeneralisedNewtypeDeriving, | GeneralizedNewtypeDeriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I suppose we could generate {{{ Test.f = coerce @String @String (Test.f @()) }}} that is, explicitly instantiating `f`. (Then maybe we could omit the second type arg to `coerce`; I'm not sure.) Ryan? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15637#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: | GeneralisedNewtypeDeriving, | GeneralizedNewtypeDeriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:1 simonpj]:
I suppose we could generate {{{ Test.f = coerce @String @String (Test.f @()) }}} that is, explicitly instantiating `f`.
That would make this particular example work, yes. Note that this strategy would not support GND'ing //every// class under the sun that uses `AllowAmbiguousTypes`, such as the example from #14266, which uses an ambiguous type variable in a class context. But your idea would still be an improvement over the status quo, so I'm inclined to adopt it.
(Then maybe we could omit the second type arg to `coerce`; I'm not sure.)
No, I don't think adding these extra type applications would change the fact that you need the second type argument to `coerce`. The reason for that is explained in `Note [GND and QuantifiedConstraints]` [http://git.haskell.org/ghc.git/blob/02edb8f2f973a8df26cfb6dfab0ef99a832f711f... here]; the short of it is the we need the second type argument to `coerce` to support GND'ing classes like: {{{#!hs class C a where c :: Int -> forall b. b -> a }}} That fact doesn't change even in the presence of this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15637#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15637: Ambiguous type variables in GeneralisedNewtypeDeriving -------------------------------------+------------------------------------- Reporter: i-am-tom | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: | GeneralisedNewtypeDeriving, | GeneralizedNewtypeDeriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5148 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D5148 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15637#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15637: Ambiguous type variables in GeneralisedNewtypeDeriving -------------------------------------+------------------------------------- Reporter: i-am-tom | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5148 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: GeneralisedNewtypeDeriving, GeneralizedNewtypeDeriving => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15637#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15637: Ambiguous type variables in GeneralisedNewtypeDeriving
-------------------------------------+-------------------------------------
Reporter: i-am-tom | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords: deriving
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D5148
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#15637: Ambiguous type variables in GeneralisedNewtypeDeriving -------------------------------------+------------------------------------- Reporter: i-am-tom | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T15637 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5148 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => deriving/should_compile/T15637 * resolution: => fixed * milestone: 8.6.1 => 8.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15637#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC