[GHC] #7862: Could not deduce (A) from the context (A, ...)

#7862: Could not deduce (A) from the context (A, ...) --------------------------------------+------------------------------------- Reporter: alang9 | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Type checker) Version: 7.6.2 | Keywords: Os: Linux | Architecture: x86_64 (amd64) Failure: GHC rejects valid program | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- The following code doesn't compile and produces a strange error: {{{ {-# LANGUAGE TypeFamilies, FlexibleContexts #-} module Numeric.AD.Internal.Tower () where type family Scalar t newtype Tower s a = Tower [a] type instance Scalar (Tower s a) = a class (Num (Scalar t), Num t) => Mode t where (<+>) :: t -> t -> t instance (Num a) => Mode (Tower s a) where Tower as <+> _ = undefined where _ = (Tower as) <+> (Tower as) instance Num a => Num (Tower s a) where }}} {{{ src/Numeric/AD/Internal/Tower.hs:17:24: Could not deduce (Num (Scalar (Tower s a))) arising from a use of `<+>' from the context (Num (Scalar (Tower s a)), Num (Tower s a), Num a) bound by the instance declaration at src/Numeric/AD/Internal/Tower.hs:14:10-36 Possible fix: add an instance declaration for (Num (Scalar (Tower s a))) In the expression: (Tower as) <+> (Tower as) In a pattern binding: _ = (Tower as) <+> (Tower as) In an equation for `<+>': (Tower as) <+> _ = undefined where _ = (Tower as) <+> (Tower as) }}} Furthermore, Removing the {{{Num (Scalar t)}}} constraint from the {{{Mode}}} class produces a different strange error: {{{ src/Numeric/AD/Internal/Tower.hs:17:24: Overlapping instances for Num (Tower s0 a) arising from a use of `<+>' Matching givens (or their superclasses): (Num (Tower s a)) bound by the instance declaration at src/Numeric/AD/Internal/Tower.hs:14:10-36 Matching instances: instance Num a => Num (Tower s a) -- Defined at src/Numeric/AD/Internal/Tower.hs:19:10 (The choice depends on the instantiation of `a, s0') In the expression: (Tower as) <+> (Tower as) In a pattern binding: _ = (Tower as) <+> (Tower as) In an equation for `<+>': (Tower as) <+> _ = undefined where _ = (Tower as) <+> (Tower as) }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7862 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7862: Could not deduce (A) from the context (A, ...) --------------------------------------+------------------------------------- Reporter: alang9 | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Type checker) Version: 7.6.2 | Keywords: Os: Linux | Architecture: x86_64 (amd64) Failure: GHC rejects valid program | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- Changes (by liyang): * cc: hackage.haskell.org@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7862#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7862: Could not deduce (A) from the context (A, ...) ----------------------------------------+----------------------------------- Reporter: alang9 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.2 Keywords: | Os: Linux Architecture: x86_64 (amd64) | Failure: GHC rejects valid program Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ----------------------------------------+----------------------------------- Changes (by simonpj): * difficulty: => Unknown Comment: The error is indeed strange. With a minor variant I got {{{ T7862.hs:18:29: Overlapping instances for Num (Tower s0 (Scalar (Tower s (Scalar (Tower s a))))) }}} Whoa! Look at that alternation of `Tower` and `Scalar`! Nothing like that shows up in the program. Turned out that it was to do with flattening type-function applications. After all, taking the strange constraint above, we see: {{{ Num (Tower s0 (Scalar (Tower s (Scalar (Tower s a))))) = Num (Tower s0 (Scalar (Tower s a))) = Num (Tower s0 a) }}} by using the `type instance` twice... and ''that'' is a much more sensible constraint. Turned out that the constraint solver was mis-orienting an equality so that, in effect, it reported a much less perspicuous (albeit still equivalent) version of constraint. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7862#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7862: Could not deduce (A) from the context (A, ...)
----------------------------------------+-----------------------------------
Reporter: alang9 | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.6.2
Keywords: | Os: Linux
Architecture: x86_64 (amd64) | Failure: GHC rejects valid program
Difficulty: Unknown | Testcase:
Blockedby: | Blocking:
Related: |
----------------------------------------+-----------------------------------
Comment(by simonpj):
{{{
commit db07129cfb13a856f31276c76e9e00924835b18e
Author: Simon Peyton Jones

#7862: Could not deduce (A) from the context (A, ...) ----------------------------------------+----------------------------------- Reporter: alang9 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.2 Keywords: | Os: Linux Architecture: x86_64 (amd64) | Failure: GHC rejects valid program Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ----------------------------------------+----------------------------------- Comment(by simonpj): OK, so now we get (from the original program) {{{ T7862a.hs:17:24: Overlapping instances for Num (Tower s0 a) arising from a use of ‛<+>’ Matching givens (or their superclasses): (Num (Tower s a)) bound by the instance declaration at T7862a.hs:14:10-36 Matching instances: instance Num a => Num (Tower s a) -- Defined at T7862a.hs:19:10 (The choice depends on the instantiation of ‛a, s0’) In the expression: (Tower as) <+> (Tower as) }}} which is better but not good. For two reasons: * The "matching given" comes from one of the "silent supperclass" parameters, which is confusing to the user. * The whole thing is really due to the ambiguity of `s0`, and that's not even reported. The reason we are careful about overlap between givens and instances is desribed in `Note [Instance and Given overlap]` in `TcInteract`. I'm not sure what to do here. I'm expecting it's not a show-stopper for you: just add a type signature to resolve the ambiguity. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7862#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC