[GHC] #10585: Implement proper bidirectional type inference

#10585: Implement proper bidirectional type inference -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (Type checker) | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The [http://research.microsoft.com/en-us/um/people/simonpj/papers/higher- rank/putting.pdf Practical Type Inference paper] (JFP '07) lays out a nice, relatively straightforward bidirectional type inference algorithm for GHC. The problem is that there is not great hygiene practiced around transitions between "down" checking and "up" checking, neither in the paper nor in the implementation. Examine Figure 8 of the paper, which presents the bidirectional typing rules. There are several syntactic forms which are fundamentally "up" forms -- forms that cannot gain any benefit from any type information being propagated downwards. Examples include App, Var, and Annot. Other forms propagate the very direction they are operated in, such as Let. And then some forms depend somewhat delicately on direction, such as the Abs rules. I propose changing these rules to be more in the style of Figure 4 from Dunfield & Krishnaswami's ICFP'13 paper [http://arxiv.org/pdf/1306.6032v1 here]. The particular rule I'm interested in is DeclSub, paraphrased here: {{{ G |-up e : s1 s1 <= s2 --------------- G |-down e : s2 }}} (I'm not advocating other aspects of their approach, just the general idea around this rule being the only transition between down and up.) In GHC, mediating between "down" checking and "up" checking is done in an ad-hoc manner, made even more difficult by the fact that it takes two separate steps to pull off properly: we must first `deeplyInstantiate` the "up" type that we get and then call `tcSubType` (or one of its variants). And, because this has to be done for each "up" expression form (forms that cannot use down-propagated type information), it's easy to miss a case. As a case in point, consider the following code: {{{ foo :: forall b. b -> (Int -> Int) -> b foo = undefined bar :: ((forall a. a -> a) -> Int) -> Int bar = undefined baz = bar (foo 3) bum = bar (3 `foo`) }}} In 7.10.1, `baz` is accepted, while `bum` is not. This is because the code for left-sections doesn't ever call `tcSubType` -- it uses `unifyType`. While that one case is easy enough to fix, I advocate a redesign of `tcExpr` to break it into two functions: one for "down" forms and one for "up" forms. These would, of course, be mutually recursive in order so that both can handle all expression forms. But these transitions could then be policed more easily. I don't actually think this would entail all that much work, and it would structurally remove the possibility of bugs such as the one above. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10585 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10585: Implement proper bidirectional type inference -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire Comment: If others (particularly, Simon) think this is a good idea, I'm happy to implement. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10585#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10585: Implement proper bidirectional type inference -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): 1. Even if we had two `tcExpr` functions (one for "up" and one for "down") why would that structurally remove the possibility of bugs? Presumably each expression form occurs in one but not the other, and you could get that wrong, just as now. In the current code, that's like missing out a subsumption check, which is a bug to be sure. 2. I think that GHC does a mixture of up and down in one blow. Consider {{{ tcExpr ((\y x. (x True, x 'x')) 3) (forall a. a->a) -> (Bool, Char)) }}} This is an APP; so we must infer the argument type of the function; but know the result type of the function, and THAT can be useful, as here. So recursively calling {{{ tcExpr (\y x. (x True, x 'x')) (alpha -> (forall a. a->a) -> (Bool, Char))) }}} is good. Here `alpha` is the `ReturnTv` that is filled in by inference. Admittedly none of this is described in the paper! 3. Lastly we need to revisit all this when we talk about [https://ghc.haskell.org/trac/ghc/wiki/ImpredicativePolymorphism/Impredicativ... impredicativity]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10585#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10585: Implement proper bidirectional type inference -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:2 simonpj]:
1. Even if we had two `tcExpr` functions (one for "up" and one for "down") why would that structurally remove the possibility of bugs? Presumably each expression form occurs in one but not the other, and you could get that wrong, just as now. In the current code, that's like missing out a subsumption check, which is a bug to be sure.
Good point. Right now, the "up" rules should end in a `tcWrapResult`, and contain a `deeplyInstantiate` if there's a possibility the inference will yield a polytype. My proposed refactoring would mean these checks would happen in one place, instead of scattered throughout the rules. But it would still be very easy for a syntactic form to be mentioned in the wrong `tcExpr`, or perhaps in both. So my claim to eliminating problems structurally is overstated.
2. I think that GHC does a mixture of up and down in one blow. Consider {{{ tcExpr ((\y x. (x True, x 'x')) 3) (forall a. a->a) -> (Bool, Char)) }}} This is an APP; so we must infer the argument type of the function;
but know the result type of the function, and THAT can be useful, as here. So recursively calling
{{{ tcExpr (\y x. (x True, x 'x')) (alpha -> (forall a. a->a) -> (Bool, Char))) }}} is good. Here `alpha` is the `ReturnTv` that is filled in by inference.
Admittedly none of this is described in the paper!
Great example! Except that GHC doesn't do what you want: this fails in 7.10.1, and this is no surprise, looking at the code. `tcApp` calls `tcInferFun`, which doesn't propagate any "down" type information. It looks like you can profitably propagate information in your example, but I think writing inference rules for this propagation would require including unification variables in the rules. This would mean that the implementation would diverge even more from any specification you could write.
3. Lastly we need to revisit all this when we talk about
[https://ghc.haskell.org/trac/ghc/wiki/ImpredicativePolymorphism/Impredicativ... impredicativity]. Indeed. I'm still in favor of this refactoring (though I don't have any understanding of how issue (3) affects us, and so could change my mind with more information there). If we decide to accommodate (2), we could easily do so by having the "App" rule in both `tcExpr`s. If we do this, we should make sure that sections are treated like applications. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10585#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10585: Implement proper bidirectional type inference -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): On (3), you can look at the wiki page and attached PDF; and at branch `wip/impredicativity`. I confess that I'm not clear exactly what "this refactoring" is in concrete terms. It's probably not massive, and it sounds promising to me, so if you'd like to sketch it out or just do it, that would be great. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10585#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10585: Implement proper bidirectional type inference -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: wontfix | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => wontfix Comment: Bah. Well, I tried doing this, and it just made everything worse. The problem is that, in the nice simple systems in published papers, there are only a few forms that can make good use of an expected type (abstractions being the poster child here). However, in GHC, it's just much, much more complicated, where the vast majority of expression forms can make good use of an expected return type. So the structural changes I was hoping would reduce the possibility of errors only improve a few cases, while making the whole structure more intricate. Not worth it. I will add a Note though explaining why there aren't two typechecker functions, though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10585#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC