[GHC] #7578: Instance selection regression from 7.4 to 7.6

#7578: Instance selection regression from 7.4 to 7.6 -----------------------------+---------------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Component: Compiler (Type checker) Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- The following code (useless due to minification) works in GHC 7.4.1: {{{ {-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances #-} class CollectArgs a where randomEvaluate :: a -> () instance CollectArgs b => CollectArgs (a -> b) where randomEvaluate f = randomEvaluate (f undefined) where () = randomEvaluate (f undefined) instance Show a => CollectArgs a where randomEvaluate x = () }}} In 7.6.2-rc1, I get this error message {{{ test.hs:8:20: Could not deduce (Show b) arising from a use of `randomEvaluate' from the context (CollectArgs b) bound by the instance declaration at test.hs:6:10-46 Possible fix: add (Show b) to the context of the instance declaration In the expression: randomEvaluate (f undefined) In a pattern binding: () = randomEvaluate (f undefined) In an equation for `randomEvaluate': randomEvaluate f = randomEvaluate (f undefined) where () = randomEvaluate (f undefined) }}} The error message goes away if I remove the {{{() = randomEvaluate (f undefined)}}} binding, i.e. the first recursive use of {{{randomEvaluate}}} works fine. (This came up at http://stackoverflow.com/questions/14294802/evaluating- function-at-random-arguments-using-quickcheck/14295179#14295179) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7578 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7578: Instance selection regression from 7.4 to 7.6 --------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.1 Resolution: invalid | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * difficulty: => Unknown * resolution: => invalid Comment: Currently this is by-design. What is happening is this. At the local binding of `()`, GHC is trying to infer the most general type of the binding. It sees a constraint `(CollectArgs b)` but at that moment it has a very local view, so it tries to simplify it. Aha. There is an instance declaration `instance Show a => CollectArgs a` which matches. Let's use that! Disaster. You are skating on very thin ice indeed, becuase there are two ways of seeming to satisify `(CollectArgs b)`, one from the context of the first instance decl, and one from the second instance decl itself. The simple way to fix this is to use `-XMonoLocalBinds` which stops GHC trying to generalise the type of the local declatation. This is good in lots of ways: see [http://research.microsoft.com/en- us/um/people/simonpj/papers/constraints/index.htm Let should not be generalised]. I'd be happy for it to be the default, and it's implied by `-XGADTs` and similar, but currently the default is still to generalise local bindings. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7578#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7578: Instance selection regression from 7.4 to 7.6 --------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.6.1 Resolution: invalid | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- Comment(by nomeata): Thanks for the clear explanation. I linked it from the SE post so that it will enlighten more Haskellers. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7578#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC