[GHC] #14273: Typed holes are oblivious to type class constraints

#14273: Typed holes are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This example is taken from Chris Allen's blog post [http://bitemyapp.com//posts/2017-09-23-please-stop-using-typed-holes.html here]: {{{#!hs pleaseShow :: Show a => Bool -> a -> Maybe String pleaseShow False _ = Nothing pleaseShow True a = Just (show _a) }}} On a recent GHC HEAD build, compiling this outputs: {{{ Bug.hs:3:32: error: • Found hole: _a :: a0 Where: ‘a0’ is an ambiguous type variable Or perhaps ‘_a’ is mis-spelled, or not in scope • In the first argument of ‘show’, namely ‘_a’ In the first argument of ‘Just’, namely ‘(show _a)’ In the expression: Just (show _a) • Relevant bindings include a :: a (bound at Bug.hs:3:17) pleaseShow :: Bool -> a -> Maybe String (bound at Bug.hs:2:1) Valid substitutions include (++) :: forall a. [a] -> [a] -> [a] (imported from ‘Prelude’ at Bug.hs:1:1 (and originally defined in ‘GHC.Base’)) fail :: forall (m :: * -> *). Monad m => forall a. String -> m a (imported from ‘Prelude’ at Bug.hs:1:1 (and originally defined in ‘GHC.Base’)) return :: forall (m :: * -> *). Monad m => forall a. a -> m a (imported from ‘Prelude’ at Bug.hs:1:1 (and originally defined in ‘GHC.Base’)) errorWithoutStackTrace :: forall (a :: TYPE r). [Char] -> a (imported from ‘Prelude’ at Bug.hs:1:1 (and originally defined in ‘GHC.Err’)) seq :: forall a b. a -> b -> b (imported from ‘Prelude’ at Bug.hs:1:1 (and originally defined in ‘GHC.Prim’)) (<>) :: forall a. Semigroup a => a -> a -> a (imported from ‘Prelude’ at Bug.hs:1:1 (and originally defined in ‘GHC.Base’)) (Some substitutions suppressed; use -fmax-valid-substitutions=N or -fno-max-valid-substitutions) | 3 | pleaseShow True a = Just (show _a) | ^^ }}} There are a couple very unsavory things about this error: 1. GHC makes no attempt to inform me that `a0` is a `Show` instance! This is the primary gripe in the blog post, and it's worth emphasizing, since without the `Show` constraint, `a0` just looks like any other random type variable. Speaking of which... 2. The list of valid substitutions is incorrect! It suggests several things which have function types, such as `(++)` and `fail`, but `(->)` does not have a `Show` instance! This list ought to be pruned based on the current type class constraints in scope. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Perhaps also the type of `pleaseShow` in the relevant bindings lacks the constraint on `a`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:1 mpickering]:
Perhaps also the type of `pleaseShow` in the relevant bindings lacks the constraint on `a`?
Ah, right you are. The error states: {{{ • Relevant bindings include a :: a (bound at Bug.hs:3:17) pleaseShow :: Bool -> a -> Maybe String (bound at Bug.hs:2:1) }}} But that second binding really ought to be `pleaseShow :: Show a => Bool -> a -> Maybe String`, no? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kosmikus): What about #9091? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: Tritlo (added) * related: => #9091 Comment: Ah, I was not aware of that ticket! Thanks, kosmikus. As noted in the original comment, there are really two bugs here: 1. The lack of reporting about type class constraints in typed hole error messages. This, as it turns out, is essentially a duplicate of #9091. 2. The incorrect "valid substitution" suggestions. I move to make this ticket about that portion specifically. To this end, I've cc'd Tritlo, the author of these valid substitution suggestions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): I'll have a look at the incorrect suggestions! About the missing constraint: if you add the -fshow-hole-constraints flag, you'll get a "Constraints include" part in the hole's type error message. Maybe it should be on by default? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:5 Tritlo]:
About the missing constraint: if you add the -fshow-hole-constraints flag, you'll get a "Constraints include" part in the hole's type error message. Maybe it should be on by default? It seems that this blog post highlights that users would like to know that about the hole.
Yes please! I didn't even know this option existed. If it's not on by default (which I imagine it should be), GHC should at least suggest it every time it encounters a typed hole that has constraints. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): Ah, I see where the problem lies. It wraps the hole with the constraints from the implications from the context, but in this case, it is the `show` function which imposes new constraints on the hole, but as you say, this is not reflected in the type of the hole (i.e. the subtype checker is checking whether `forall a. Num a => a -> a -> a` fits the hole of type `Show a => a0_a1m3[tau:2]`, where (as we can see), the mentioned `a` is not `a0_a1m3[tau:2]`, which is the ambiguous type variable in question. I'll get to work on fixing that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Tritlo): * owner: (none) => Tritlo -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): And the plot thickens: if I add a module declaration, I get an additional error message, i.e., when the code is the following: {{{ module TestShow where pleaseShow :: Show a => Bool -> a -> Maybe String pleaseShow False _ = Nothing pleaseShow True a = Just (show _a) }}} I get the same error as before, but now with an additional message before the typed hole error message: {{{ t4.hs:5:28: error: • Could not deduce (Show a0) arising from a use of ‘show’ from the context: Show a bound by the type signature for: pleaseShow :: forall a. Show a => Bool -> a -> Maybe String at t4.hs:3:1-49 The type variable ‘a0’ is ambiguous These potential instances exist: instance (Show b, Show a) => Show (Either a b) -- Defined in ‘Data.Either’ instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 23 others ...plus 54 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the first argument of ‘Just’, namely ‘(show _a)’ In the expression: Just (show _a) In an equation for ‘pleaseShow’: pleaseShow True a = Just (show _a) | 5 | pleaseShow True a = Just (show _a) | ^^^^^^^ }}} Which does tell you the constraint on the hole (if you connect the ambiguous type variable names yourself). I suspect I'll have to invoke the same mechanism, and then add the constraints derived with that mechanism and wrap the type with that as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) * related: #9091 => #9091, #9479 * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It's easy to get confused here. First consider {{{ foo :: [a] -> String foo xs = show (_h ++ []) }}} We end up with this residual constraint {{{ forall a. [W] Show alpha [Hole] _h :: [alpha] }}} where `alpha` is a unification variable, standing for an as-yet-unknown type. The two unsolved constraints are * The `[Hole]` constraint feeds the error-report mechanism, reporting that `_h` must be filled vith a value of type `[alpha]`. * The `Show alpha` constraint arises from the call of `show`. Initially we'd get a `Show [alpha]` constraint, but we use the instance declaration `instance Show x => Show [x]` to reduce it to `Show alpha`. Now, what can we fill the hole with? Clearly something of form `[ty]`. But once we know what we fill it with, we can set `alpha := ty`, and then we want for the rest of the constraints to be soluble, in this case `Show alpha`. So filling with `[Int]` would be fine, but filling with `[Int -> Int]` would not. Filling with `[a]` would not work either, since we have no way to solve `Show a`. However, if the original definition had been {{{ foo :: Show a => [a] -> String foo xs = show (_h ++ []) }}} we'd end up with the residual constraint {{{ forall a. Show a => [W] Show alpha [Hole] _h :: [alpha] }}} then we ''could'' fill `_h` with `xs :: [a]`, because we now do have a `Show a` in scope from the type signature. TL;DR: the real question is this: * After filling the hole, can we solve the '''rest of the constraint'''? Sadly, that's not a very easy question to answer. * The current architecture focuses on the `[Hole]` constraint all by itself, but this example shows that it's really all about that constraint's peers. * There may be many unsolved constraints; filling one hole will not nail all of them, so we might erroneously reject a filler. For example {{{ [W] C alpha beta [Hole] _h1 :: alpha [Hole] _h2 :: beta }}} Here we'll never succeed in solving `C alpha beta` until we have simultaneously filled both holes with compatible types. * Operationally, constraint solving may perform unification. And unification is (currently) done by side-effect, and not easily undone. So trying successive candidates for hole-filling risks prematurely fixing the unification variables. In full generality this looks too hard. But I think you might be able to do a reasonable job for common cases. For example * Given a contraint {{{ forall as1. G1 => ... (forall as2. G2 => [Hole] _h :: ty C1, ..., Cn )... }}} pick the subset of Ci whose free unification variables are all mentioned in `ty`, say D1..Dm * Pick a candidate `cand :: cand_ty` to fill `_h`. * Clone any free unification variables * Try to solve the constraint {{{ forall as1. G1 => (forall as2. G2 => cand_ty <= ty -- subsumes D1, ..., Dm ) }}} This isn't perfect, but it'd work in common cases I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): I said in old tickets that Typed Holes should not be enabled by default in the compiler. It does not make sense to activate it by default. At most it will only be an additional help but not a wonder and has shown so far that Typed Holes gives us more worry than clarity because of the errors (or warning) returned by the compiler. In this attitude the author is not wrong. I agree with him, because in some circumstances Typed Holes does not make sense. As for the usefulness of Typed Holes, his help is not miraculous. in all cases, Typed Holes should not be enabled by default. Take a look in Miranda, there is no Typed Holes and everything goes very well. Sometimes when one wants to do too well one does too badly. So Typed Holes in Haskell, why not? Provided you do not activate it by default! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): Replying to [comment:11 simonpj]: Thanks for the clarifications. I'll aim for making it work for the common cases then. Replying to [comment:12 vanto]: Well, they're (kind of) not on by default, you have to have a typed hole in your code for it to trigger. What other behaviour do you want when `_` is encountered in expressions? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to [[span(style=color: #FF0000, Tritlo )]]:\\ In GHC 5.0.3 or GHC 6.0, for instance:\\ {{{ Prelude> (\x -> x + _) 3 <interactive>:1: Pattern syntax in expression context: _ }}} This response from the compiler is clear and sufficient.\\ For those who want to go further and find an answer, then they activate Typed Holes in the compiler and start again. {{{ Prelude> f = (\x -> x + _) 2 <interactive>:1:16: error: * Found hole: _ :: a Where: `a' is a rigid type variable bound by the inferred type of f :: Num a => a at <interactive>:1:1-19 * In the second argument of `(+)', namely `_' In the expression: x + _ In the expression: \ x -> x + _ * Relevant bindings include x :: a (bound at <interactive>:1:7) f :: a (bound at <interactive>:1:1) }}} It is better to do as before rather than to do the reverse, ie write {{{-fdefer-type-errors}}} or {{{ -fdefer-typed-holes}}} Being brief, use Typed Holes if needed. I have no retrograde ideas when I say that. I'm thinking of a better use of the compiler. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): vanto, I don't think many others will agree with you. But if you feel strongly about it, you can write up a GHC proposal at https://github.com /ghc-proposals/ghc-proposals -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Thank you very much. It is a matter of point of view. If I drive on a road I know with my car, I do not operate the GPS. I do not have to listen to the details of the road. I think it makes sense. But I also have the choice of putting it into operation. So if I had the same possibility with the compiler about Typed Holes, then it would be perfect. No proposal for that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mentheta): * cc: mentheta (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): RyanGIScott: I've implemented a fix which is currently on Phabricator as [https://phabricator.haskell.org/D4315 D4315], and I've included your example as a test. Could you have a look at the diff and check that the output is the output you'd expect? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Phab:D4315 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4315 Comment: I've left some comments on Phabricator. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Phab:D4315 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): So I've responded to the comments and made some additional improvements and I think everything is in order for it to be patched now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class
constraints
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: Tritlo
Type: bug | Status: patch
Priority: normal | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.3
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Poor/confusing | Unknown/Multiple
error message | Test Case:
Blocked By: | Blocking:
Related Tickets: #9091, #9479 | Differential Rev(s): Phab:D4315
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: merge Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Phab:D4315 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: merge Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Phab:D4315 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged in 96b52e63b850f8072b905ca232b5644efc011b37. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14273: Typed holes' "valid substitutions" suggestions are oblivious to type class constraints -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Tritlo Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #9091, #9479 | Differential Rev(s): Phab:D4315 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14273#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC