[GHC] #9821: DeriveAnyClass support for higher-kinded classes + some more comments

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: new Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.9 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: #5462 | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- #5462 was merged before a few final fixes were done. This ticket serves to record that. Left to address are: https://phabricator.haskell.org/D476?id=1443#inline-3652 https://phabricator.haskell.org/D476?id=1443#inline-3648 https://phabricator.haskell.org/D476?id=1443#inline-3646 Also, `DeriveAnyClass` currently panics at higher-kinded classes (like `((* -> *) -> *) -> Constraint`). I'll fix this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: new Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #5462, #9968 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by dreixel): * related: #5462 => #5462, #9968 * milestone: 7.12.1 => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: infoneeded Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: What is the status here? Note that #9968 was fixed recently. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: infoneeded Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Generics -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): #12144 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #5462, #9968 => #5462, #9968, #12144 Comment: To the best of my knowledge, here's a summary of the current state of each of those comments: 1. https://phabricator.haskell.org/D476?id=1443#inline-3652 - The logic of this check is explained more thoroughly in [http://git.haskell.org/ghc.git/blob/498ed2664219f7e8f1077f46ad2061aba2f57de4... Note (Determining whether newtype-deriving is appropriate)], which will be further clarified with Phab:D2280. 2. https://phabricator.haskell.org/D476?id=1443#inline-3648 and https://phabricator.haskell.org/D476?id=1443#inline-3646 ask to clarify that `DeriveAnyClass` does indeed only work on argument types of kind `*` and `* -> *` at the moment. #9968 fixed these. So the only thing that remains is to implement support for deriving types of other kinds with `DeriveAnyClass`. I believe that #12144 is very relevant here, since I don't see a way to properly fix that ticket without overhauling the way `DeriveAnyClass` infers its instance contexts in `deriving` clauses. Simon's comment [https://mail.haskell.org/pipermail /ghc-devs/2016-June/012276.html here] provides one suggestion on how to do this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): #12144 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Sounds good to me. Let's go with the [https://mail.haskell.org/pipermail /ghc-devs/2016-June/012252.html email thread] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 12918 | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961 #12144 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D2961 Comment: A WIP attempt at fixing this is at Phab:D2961. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 12918 | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961 #12144 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: infoneeded => patch * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961 #12144 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): This is respoinding to [https://phabricator.haskell.org/D2961#inline-25611], concerning the way to use implication constraints to simplify the `DeriveAnyClass` implementation. The original idea is in [https://phabricator.haskell.org/D2961#inline-25543], where I said: I think it would help to explain more carefully what is happening here. How come we don't need to look at the data constructors any more? Example: {{{ class Foo a where bar :: Ix b => a -> b -> String default bar :: (Show a, Ix b) => a -> b -> String bar x y = show x baz :: Eq a => a -> a -> Bool default baz :: (Ord a, Show a) => a -> a -> Bool baz x y = compare x y == EQ }}} Given {{{ deriving instance Foo (Maybe d) }}} we behave as if you had written {{{ instance ??? => Foo (Maybe d) where {} }}} (that is, using the default methods from the class decl), and that in turn means {{{ instance ??? => Foo (Maybe d) where bar = $gdm_bar baz = $gdm_baz }}} where {{{ $gdm_bar :: forall a. Foo a => forall b. (Show a, Ix b) => a -> b -> String }}} is the generic default method defined by the class declaratation. Our task is to figure out what "???" should be. Answer: enough constraints to satisfy the Wanteds arising from the calls of $gdm_bar and $gdm_baz. So we end up with two sets of constraints to simplify: {{{ bar: (Givens: [Ix b], Wanteds: [Show (Maybe d), Ix b]) baz: (Givens: [Eq (Maybe d)], Wanteds: [Ord (Maybe d), Show (Maybe d)]) }}} Important: note that * the Givens come from the ordinary method type, while * the Wanteds come from the generic method. These are just implication constraints. We can combine them into a single constraint: {{{ (forall b. Ix b => Show (Maybe d), Ix b) /\ (forall . Eq (Maybe d) => Ord (Maybe d), Show (Maybe d)) }}} Notice that the type variables from the head of the instance decl (just `d` in this case) are global to this constraint, but any local quantification of the generic default method (e.g. `b` in the case of `bar`) are locally scoped to each implication, as they obviously should be. Now we solve this constraint, getting the residual constraint (RC) {{{ (forall b. Ix b => Show d) /\ (forall . Eq (Maybe b) => Ord d, Show d) }}} Now we need to hoist those constraints out of the implications to become our candidates for the "???". That is done by `approximateWC`, which will return {{{ (Show d, Ord d, Show d) }}} Now we can use `mkMinimalBySCs` to remove superclasses and duplicates, giving {{{ (Show d, Ord d) }}} And that's what we need for the "???". -------------- But we aren't done yet! Suppose we had written {{{ bar :: a -> b -> String default bar :: (Show a, C a b) => a -> b -> String }}} I've replaced `Ix b` by `C b` and I've removed it from the vanilla sig for `Bar`. Now the implication constraint will be {{{ forall b. () => Show (Maybe d), C (Maybe d) b }}} Suppose we have `instance Read p => C (Maybe p) q`. Then after simplification, we get the residual constraint (RC): {{{ forall b. () => (Show d, Read d) }}} and all is well. But suppose we had no such instance, or we had an instance like `instance C p q => C (Maybe p) q`. Then we'd finish up with the residual consraint (RC): {{{ forall b. () => (Show d, C d b) }}} and now `approximateWC` will produce only `Show d` from this, becuase `(C d b)` is captured by the `forall b`. What do to? Easy! Once we have decided "???" should be CX, say, just emit this implication (to be solved later): {{{ forall d. CX => RC }}} where RC is the residual constraint we computed earlier. Bingo! From CX we'll be able to solve all the constraints that `approximateWC` extracted, and we'll be left with the error that we want to report for that `(C d b)` constraint. ------------------ This may seem complicated, but it's '''exactly what happens in `TcSimplify.simplifyInfer`'''. It does a bit more besides (figuring out what type variables to quantify over), but it makes a good guide. We might ultimately wat to share code, but for now I think it's easier to do one step at a time. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961 #12144 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Thanks you Simon for the extra details. But I'm still quite fuzzy on some of the particulars. To be specific: 1. You've indicated that `approximateWC` is the way to go for retrieving the residual constraints out of an implication. But the type signature for `approximateWC` is more complicated than I expected: {{{#!hs approximateWC :: Bool -> WantedConstraints -> Cts -- Postcondition: Wanted or Derived Cts -- See Note [ApproximateWC] approximateWC float_past_equalities wc }}} In particular, there's this mysterious `float_past_equalities` argument. I've tried reading `Note [ApproximateWC]` to figure out what this means, but it talks about inferring most general types, which I'm not sure is relevant to this story or not. Should `float_past_equalities` be `True` or `False`? 2. I didn't really follow what you were trying to say here: Replying to [comment:14 simonpj]: > But we aren't done yet! Suppose we had written > {{{ > bar :: a -> b -> String > default bar :: (Show a, C a b) => a -> b -> String > }}} > I've replaced `Ix b` by `C b` and I've removed it from the vanilla sig for `Bar`. Now the implication constraint will be > {{{ > forall b. () => Show (Maybe d), C (Maybe d) b > }}} > Suppose we have `instance Read p => C (Maybe p) q`. Then after simplification, we get the residual constraint (RC): > {{{ > forall b. () => (Show d, Read d) > }}} > and all is well. But suppose we had no such instance, or we had an instance like `instance C p q => C (Maybe p) q`. Then we'd finish up with the residual consraint (RC): > {{{ > forall b. () => (Show d, C d b) > }}} > and now `approximateWC` will produce only `Show d` from this, becuase `(C d b)` is captured by the `forall b`. What do to? > > Easy! Once we have decided "???" should be CX, say, just emit this implication (to be solved later): > {{{ > forall d. CX => RC > }}} > where RC is the residual constraint we computed earlier. Bingo! From CX we'll be able to solve all the constraints that `approximateWC` extracted, and we'll be left with the error that we want to report for that `(C d b)` constraint. > > ------------------ > This may seem complicated, but it's '''exactly what happens in `TcSimplify.simplifyInfer`'''. It does a bit more besides (figuring out what type variables to quantify over), but it makes a good guide. We might ultimately wat to share code, but for now I think it's easier to do one step at a time. > > First of all, you jumped from a concrete example to `forall d. CX => RC` halfway through. What are `CX` and `RC` here? Why did we switch from `forall b.` to `forall d.`? Also, should I interpret this as meaning that if there are any implication constraints leftover after solving which contain something of the form `forall x. C => Foo x` (i.e., if there are constraints which contain type variables other than the class's type variables), that should be an error? Do we already take care of this with [http://git.haskell.org/ghc.git/blob/bbd3c399939311ec3e308721ab87ca6b9443f358... these lines] in `TcDerivInfer`: {{{#!hs ; (implic, _) <- buildImplicationFor tclvl skol_info tvs_skols [] unsolved -- The buildImplicationFor is just to bind the skolems, -- in case they are mentioned in error messages -- See Trac #11347 -- Report the (bad) unsolved constraints ; unless defer (reportAllUnsolved (mkImplicWC implic)) }}} Or does something else need to happen? Finally, I'm rather confused by your comments about `simplifyInfer`. Are you saying that I should literally use` simplifyInfer` to solve these implications, or that I should be copy-pasting code from `simplifyInfer` for this use case? If it's the former, how do I invoke `simplifyInfer`? Its type signature is rather daunting: {{{#!hs simplifyInfer :: TcLevel -- Used when generating the constraints -> InferMode -> [TcIdSigInst] -- Any signatures (possibly partial) -> [(Name, TcTauType)] -- Variables to be generalised, -- and their tau-types -> WantedConstraints -> TcM ([TcTyVar], -- Quantify over these type variables [EvVar], -- ... and these constraints (fully zonked) TcEvBinds) -- ... binding these evidence variables }}} In particular, I'm unfamiliar with what the `InferMode`, `[TcIdSigInst]`, and `[(Name, TcTauType)]` arguments should be, and if the returned `TcEvBinds` is relevant. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961 #12144 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
but it talks about inferring most general types, which I'm not sure is relevant to this story or not
Yes it's relevant. In inferring "???" we are indeed trying to infer the most general type for the instances. We seek the context with fewest constraints (i.e. most general). The equalities thing doesn't matter much, but for consistency with `simplifyInfer` set it to `True`.
What are CX and RC here?
Also, should I interpret this as meaning that if there are any implication constraints leftover after solving which contain something of
I defined them earlier in the text you quoted! RC = residual context, CX is what we decide ??? should be. the form forall x. C => Foo x (i.e., if there are constraints which contain type variables other than the class's type variables), that should be an error? Yes, certainly. Notice that `approximateWC` doesn't remove the constraints it floats out; it just floats them out. They are still there in RC; but we'll solve them easily from CX.
Do we already take care of this with these lines in TcDerivInfer:
I'm not sure.. too much is in flux. But you don't need to solve it because you don't need to know the answer here: just emit it and it'll get solved later.
Are you saying that I should literally use simplifyInfer to solve these implications
No: sharing code with `simplifyInfer` in due course would be a good plan, but it does a lot more so just use it as a source of inspiration, no more. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Currently in simplifyDeriv, we are using the function simplifyWantedsTcM to simplify the constraints, which seemed to work well back when all of our deriving-related constraints were simple wanteds. But now we're
2. When you say "just emit this implication": `forall d. CX => RC`.. To tie it back to your example in comment:10, are you proposing to emit
#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961 #12144 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Further clarifications throwing implication constraints into the mix. Are you proposing to replace the use of simplifyWantedsTcM entirely with something la simplifyInfer? Are you proposing to invoke a simplifyInfer-like function after simplifyWantedsTcM? Something else? Something like `simplifyInfer`, but simpler. Call `simplifyWanteds`; then `approximateWC`; then `mkMinimalBySCs`; then emit the residual constraint as above. this? {{{ forall d. Show d => ((forall b. () => (Show d, C d b)) ^ (forall . Eq (Maybe d) => (Ord d, Show d)) }}}
That is, letting {{{ CX = (Show d) RC = ((forall b. () => (Show d, C d b)) ^ (forall . Eq (Maybe d) => (Ord d, Show d)) }}}
I see that there is a function emitImplication, which appears to modify
Maybe you meant comment:14. Then yes. (There are several related examples in comment:14, so I'm not sure precisely which one you mean. the state of TcM. But I'm still unsure of when the error message involving (C d b) is supposed to be thrown. That is, what specific action causes the typechecker to see the bogus (C d b) and complain? It's the `simplifyTop` called right at the top level, in `TcRnDriver`. Most constraint solving is done by this single call to `simplifyTop`; only when we MUST solve eagerly (as here, to get CX) do we call the solver. Usually we just toss the unsolved constraint into the monad and solve it right at the end. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9821: DeriveAnyClass support for higher-kinded classes + some more comments
-------------------------------------+-------------------------------------
Reporter: dreixel | Owner: dreixel
Type: bug | Status: patch
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 7.9
Resolution: | Keywords: Generics
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961
#12144 |
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#9821: DeriveAnyClass support for higher-kinded classes + some more comments -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5462, #9968, | Differential Rev(s): Phab:D2961 #12144 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9821#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC