[GHC] #12791: Superclass methods could be more aggressively specialised.

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Say `R` is a superclass of `MR` but only uses one of the type variables. If this type variable is fixed then we know that we are going to use the specific dictionary. Thus, the optimiser *could* specialise all methods from the superclass at this point leading to better code. {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} module Foo where class R t => MR t m where push :: t -> m -> Int class R t where pull :: t -> Int --type MR2 t m = (R t, MR t m) instance MR Int Int where push = max instance R Int where pull = negate myf :: (MR Int a) => a -> Int -> Int myf _ = pull }}} To give a concrete example, `R` is a super class of `MR` but only mentions the first type variable. Thus when we fix it in `myf`, we could optimise the definition to `myf _ = negate` by inlining the class method. Reid points out that if you have a definition like {{{ data X = X f :: R X => Int -> Int f = pull }}} then the instance for `R X` could be provided by another module. However it is common to structure large applications with super class constraints so it would be desirable to do better. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by mpickering: @@ -2,2 +2,3 @@ - If this type variable is fixed then we know that we are going to use the - specific dictionary. Thus, the optimiser *could* specialise all methods + If this type variable is fixed then we know that we are going to use a + specific instance for `R`. Thus, the optimiser *could* specialise all + methods New description: Say `R` is a superclass of `MR` but only uses one of the type variables. If this type variable is fixed then we know that we are going to use a specific instance for `R`. Thus, the optimiser *could* specialise all methods from the superclass at this point leading to better code. {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} module Foo where class R t => MR t m where push :: t -> m -> Int class R t where pull :: t -> Int --type MR2 t m = (R t, MR t m) instance MR Int Int where push = max instance R Int where pull = negate myf :: (MR Int a) => a -> Int -> Int myf _ = pull }}} To give a concrete example, `R` is a super class of `MR` but only mentions the first type variable. Thus when we fix it in `myf`, we could optimise the definition to `myf _ = negate` by inlining the class method. Reid points out that if you have a definition like {{{ data X = X f :: R X => Int -> Int f = pull }}} then the instance for `R X` could be provided by another module. However it is common to structure large applications with super class constraints so it would be desirable to do better. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * Attachment "newfoo.dump-simpl" added. Core Dump -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I found that explanation slightly more complicated than necessary. Consider this example: {{{#!hs {-# LANGUAGE MultiParamTypeClasses, FlexibleContexts #-} module G where class Num a => C a b where m :: a -> b f :: C Int b => b -> Int -> Int f _ x = x + 1 }}} In `f`, there is a `Num Int` instance available from the passed-in `C Int b` instance. So, GHC generates this code for `f`: {{{ G.f = \ (@ b_aLy) ($dC_aLz :: G.C GHC.Types.Int b_aLy) _ [Occ=Dead] (eta1_B1 :: GHC.Types.Int) -> GHC.Num.+ @ GHC.Types.Int (G.$p1C @ GHC.Types.Int @ b_aLy $dC_aLz) eta1_B1 G.f1 }}} which is obviously terrible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Thanks Reid. That is a clear description of the problem I had in mind. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ryantrinkle): Just wanted to note that fixing this seems likely to help dramatically with monad transformer and reflex performance in my company's codebases. We see a ton of this in our dump-simpl outputs. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): This is nothing to do with specialisation. It has to do with how the constraint solver solves constraints. But it's not easy to fix you problem. GHC's constraint solver uses the "given" constraint (here `Num Int` via a superclass of `C Int b`) where possible. You may say "If there is an instance declaration, use that instead of the given constraint. But no {{{ f :: Ord [a] => ... f x = ..Need Eq [a]... }}} There is a top-level instance for `Eq [a]`, but if we use it we'll need `Eq a` and we haven't got that. So we must satisfy the `Eq [a]` from the superclass of `Ord [a]`. I suppose we could make a special case when the instance declaration does not generate any new constraints, as is the case for `Num Int`. Would that deal with your "ton of cases"? Can you give more concrete examples? I worry that it might not be long before someone complains that GHC is bypassing the dictionary they have passed in. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ryantrinkle): Hmm, that makes a lot of sense. I think we probably would run into that sometimes, although I'm not entirely sure how often. We may be able to factor out these superclasses - in the cases I know of, they're for convenience, not out of necessity. There's a lot I don't understand here, but I do suspect that in our real- world cases, extremely aggressive inlining (like I'm hoping to get working, see https://mail.haskell.org/pipermail/ghc- devs/2016-October/013142.html) may result in enough inlining that this issue doesn't matter. Ideally, I'd like both the subclass and the superclass to be inlined. I'm just worried that sometimes the subclass won't be inlinable, and if that also prevents the superclass from being inlined, that'll make the optimization very brittle. With regard to having the wrong dictionary being passed in, I suppose changing this behavior would lean very heavily on the canonicity of instances - and perhaps would interfere with uses of incoherent instances and such? I'm fairly certain it wouldn't be a problem in any of our code, but I wouldn't want to cause problems for others. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): To look at this from another perspective, if you write a function using methods from `Num` at a known type then GHC will specialise this code to the specific (+) defined for `Int`. If there is no instance then the definition will fail to type check. {{{#!hs foo :: Int -> Int -> Int foo = (+) }}} another valid choice would be to infer a constraint as there could be an instance for `Num` defined in another module which could then use this function. {{{#!hs foo1 :: Num Int => Int -> Int -> Int foo1 = (+) }}} This seems analogous to the worry that "it might not be long before someone complains that GHC is bypassing the dictionary they have passed in.". We already assume coherence so using it again here seems more consistent and will produce much better code! Secondly, these super classes exist mainly for convenience so that users do not have to type out many constraints. It currently seems that in order to write code which will definitely specialise then you have to write out each constraint individually and avoid using super classes. Constraint kinds are also not an option as you end up with exactly the same problem. It seems a shame that there are no free methods for abstracting a bunch of different constraints and still getting guarantees about performance. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Like I say, I could imagine a special case for the situation where the constraint is `C t1 .. tn` and it can be solved by a top-level instance that has no context. It'd be ad-hoc but probably useful, and I agree that the "might use the wrong dictionary" thing is probably an edge case. Beyond that, as I show above, I don't think we can use top-level instances. What I don't know is whether this special case would solve the "ton of cases" that you have seen in your code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): It would certainly help in some places. How hard do you think this would be to implement? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Not hard; but it'd be encouraging if there were some "from the field" use cases to motivate. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Here is one example, https://github.com/reflex-frp/reflex- dom/blob/c51a5585860db17ce63601524340f09cb75f0129/src/Reflex/Dom/Builder/Class.hs#L68 `DomBuilder` has two type parameters `m` and `t`, `Reflex t` is used as a super class constraint. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK, so to complete the connection with comment:2, are there a ton of functions with user-written signatures like this? {{{ f :: (DomBuilder Int m) => blah }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Yes and here is another example from transformers. {{{#!hs class (Monoid w, Monad m) => MonadWriter w m | m -> w where }}} It is suggested to write functions of the form, {{{#!hs f :: (MonadWriter MyMonoid m) => m .... }}} which will have the same problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ryantrinkle): simonpj: Yes. I've always encouraged the abstract style ( {{{ (MonadReader r m, MonadWriter w m) => m a }}} rather than {{{ ReaderT r (WriterT w m) a }}} ), so that the concrete monad transformer stack can be changed without modifying user code. It has worked really well to help keep code clean and organized (especially with GHC 8.0's warnings for unused constraints). So, in a typical reflex widget, there will be several constraints, e.g. DomBuilder t m, PerformEvent t m, PostBuild t m. Reflex is currently a superclass of all of these, since the 't' parameter is only meaningful for its Reflex instance. I haven't looked into whether it's possible to eliminate Reflex from all of these classes, but I'll certainly try to do that if it'll help with optimization. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:5 simonpj]:
GHC's constraint solver uses the "given" constraint (here `Num Int` via a superclass of `C Int b`) where possible. You may say "If there is an instance declaration, use that instead of the given constraint. But no {{{ f :: Ord [a] => ... f x = ..Need Eq [a]... }}}
If we didn't have overlapping instances, could we reduce the `Ord [a]` constraint to `Ord a` when checking the signature (changing the semantics of `FlexibleContexts` a bit)? That would open up a different path to `Eq [a]`. Or do these constraints sometimes arise in situations where they can't be (or shouldn't be) reduced? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * owner: => danharaj -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Changes (by danharaj): * differential: => Phab:D2714 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Could you try to say, in a precise way, what the patch is seeking to achieve; what programs will typecheck that don't now, with a number of examples; and what program won't typecheck despite the patch? This is a long thread and I'm really very lost. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by danharaj): Hi, The motivation of this patch is that the compiler can produce more efficient code if the constraint solver used top-level instance declarations to solve constraints that are currently solved givens and their superclasses. In particular, as it currently stands, the compiler imposes a performance penalty on the common use-case where superclasses are bundled together for user convenience. The performance penalty applies to constraint synonyms as well. This example illustrates the issue: {{{#!hs {-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FunctionalDependencies #-} module A where import Data.Monoid class (Monoid w, Monad m) => MonadWriter w m | m -> w where tell :: w -> m () f :: MonadWriter Any m => [Any] -> m () f xs = tell (mconcat xs) }}} This produces the following core on GHC 8.0.2 by running `ghc A.hs -ddump- simpl -dsuppress-idinfo`: {{{ f :: forall (m_aJV :: * -> *). MonadWriter Any m_aJV => [Any] -> m_aJV () f = \ (@ (m_aZM :: * -> *)) ($dMonadWriter_aZN :: MonadWriter Any m_aZM) (eta_B1 :: [Any]) -> tell @ Any @ m_aZM $dMonadWriter_aZN (mconcat @ Any (A.$p1MonadWriter @ Any @ m_aZM $dMonadWriter_aZN) eta_B1) }}} With the patch, the code produced: {{{ f :: forall (m :: * -> *). MonadWriter Any m => [Any] -> m () f = \ (@ (m :: * -> *)) ($dMonadWriter_a12F :: MonadWriter Any m) (xs_aLg :: [Any]) -> tell @ Any @ m $dMonadWriter_a12F (mconcat @ Any Data.Monoid.$fMonoidAny xs_aLg) }}} The performance gains possible are perhaps more starkly present in the following example from the comment thread, which here I have compiled also with `-O2`: {{{#!hs {-# LANGUAGE ConstraintKinds, MultiParamTypeClasses, FlexibleContexts #-} module B where class M a b where m :: a -> b type C a b = (Num a, M a b) f :: C Int b => b -> Int -> Int f _ x = x + 1 }}} Output without the patch: {{{ f :: forall b_arz. C Int b_arz => b_arz -> Int -> Int f = \ (@ b_a1EB) ($d(%,%)_a1EC :: C Int b_a1EB) _ (eta1_B1 :: Int) -> + @ Int (GHC.Classes.$p1(%,%) @ (Num Int) @ (M Int b_a1EB) $d(%,%)_a1EC) eta1_B1 B.f1 }}} Output with the patch: {{{ f :: forall b. C Int b => b -> Int -> Int f = \ (@ b) _ _ (x_azg :: Int) -> case x_azg of { GHC.Types.I# x1_a1DP -> GHC.Types.I# (GHC.Prim.+# x1_a1DP 1#) } }}} However, there is a reason why the solver does not simply try to solve such constraints with top-level instances. If the solver finds a relevant instance declaration in scope, that instance may require a context that can't be solved for. As pointed out in the thread, a good example of this is: {{{ f :: Ord [a] => ... f x = ..Need Eq [a]... }}} If we have `instance Eq a => Eq [a]` in scope and we tried to use it, we would be left with the obligation to solve the constraint `Eq a`, which we cannot. So the patch must be conservative in its attempt to use an instance declaration to solve the constraint we're interested in. The rule I have applied is as was previously mentioned in the comment thread: The solver gives up on using an instance declaration to solve a given constraint if doing so would produce more work to be done; we make no attempt even if the new constraints are also solvable with instances. Precisely: The intent of the patch is to only attempt to solve constraints of the form `C t1 ... tn` and only with instances with no context. This example illustrates the conservative behavior: {{{#!hs {-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FunctionalDependencies #-} module C where class Eq a => C a b | b -> a where m :: b -> a f :: C [Int] b => b -> Bool f x = m x == [] }}} The core output without the patch: {{{ f :: forall b_a1ka. C [Int] b_a1ka => b_a1ka -> Bool f = \ (@ b_a1rX) ($dC_a1rY :: C [Int] b_a1rX) (eta_B1 :: b_a1rX) -> == @ [Int] (C.$p1C @ [Int] @ b_a1rX $dC_a1rY) (m @ [Int] @ b_a1rX $dC_a1rY eta_B1) (GHC.Types.[] @ Int) }}} The core output with the patch: {{{ f :: forall b. C [Int] b => b -> Bool f = \ (@ b) ($dC_a1sq :: C [Int] b) (eta_B1 :: b) -> == @ [Int] (C.$p1C @ [Int] @ b $dC_a1sq) (m @ [Int] @ b $dC_a1sq eta_B1) (GHC.Types.[] @ Int) }}} Even though we also have an instance for `Eq Int` in scope, the solver does not even try. The impact of this patch on typeability is simple: there should be no change whatsoever. Every program considered well-typed without the patch should remain well-typed with it, and every program considered ill-typed without the patch should remain ill-typed. There is a possible change in semantics with this patch because the solver is now choosing different solutions for certain constraints, however there should be no difference in behavior up to confluence of proofs. There is a possible interaction with overlapping instances and my intent was to preserve the current behavior of overlapping instances exactly. I expect that code that uses Incoherent Instances could see a change in behavior with this patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That is an admirably clear explanation, thank you. Could you please add it (suitably edited) as a `Note` in the code? I think I buy the idea in principle. But do we have "in the wild" example(s) of where it makes a perceptible difference? Will anyone notice/care? I don't think the implementation is right, I'm afraid, but I'll comment on Phab. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): PS: about incoherence, you could simply disable this optimisation if the user says `-XIncoherentInstances`, which is relatively rare. That would seem plausible to me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by danharaj): Replying to [comment:20 simonpj]:
That is an admirably clear explanation, thank you. Could you please add it (suitably edited) as a `Note` in the code?
I think I buy the idea in principle. But do we have "in the wild" example(s) of where it makes a perceptible difference? Will anyone notice/care?
I don't think the implementation is right, I'm afraid, but I'll comment on Phab.
Simon
I've got a working draft of a patch that follows your guidance and includes my explanation as a note. I will polish it and put it on Phab once I have a convincing case that real code benefits from this change. Unfortunately, the code I'm trying to improve for the `reflex` package has an instance of this form that I would like to use in lieu of given superclasses: {{{#!hs instance t ~ SpiderTimeline Global => Reflex t where ... }}} This is a strange instance. Normally the `reflex` package is completely polymorphic in `t`. However there are performance issues with this approach if intermediate definitions are not inlined aggressively enough to end up at a call site where all the types are concrete (usually in `main = ...`). An experimental flag provides this instance in an attempt to get better code when user's write code whose constraints imply `Reflex t`. The classes that cause suboptimal code all have a similar form to this class declaration: {{{#!hs class (Monad m, Reflex t, DomSpace (DomBuilderSpace m), MonadAdjust t m) => DomBuilder t m | m -> t where ... }}} The code users of `reflex` tend to write looks like: {{{#!hs buildSomeDom :: DomBuilder t m => ... -> m () }}} I don't know if there's anything reasonable we can do for this case, even with the strange instance. Nevertheless it's useful to me to have some real world code to work with. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Dan, you should open a new ticket to talk about this change as it is unrelated. I think it is still unclear what is going on in the case of reflex but let's not side track this ticket. It isn't clear that instances such as the strange one in your ticket help at all. If at the call site, a specific `t` is known then the class methods of `Reflex` should be suitably specialised, if not then we should understand why it is not happening without resorting to hacks! I think there are plenty of real world examples of this, that isn't a worry. A simple one is {{{ foo :: MonadWriter String m => m () foo = ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ryantrinkle): I'm afraid it's my fault that these things have gotten mixed up. I asked Dan to look into this stuff in the hope that it would give some benefit in the Reflex case, but he found today that it doesn't quite fit. You're absolutely right that the Writer case is still useful. You're absolutely right about putting specialization under separate tickets, and we'll be doing that if we find anything in that vein. In the mean time, if Dan's work so far helps in the MonadWriter case, we'll try to get that wrapped up for this ticket soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835 | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #5835 Comment: It seems like #5835 is somewhat related here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835 | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nfrisby): * cc: nfrisby (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835 | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by danharaj): #5835 is indeed related and my patch resolves it too. However, my patch causes a regression in #10359. The core has bad bits that all look similar to this: {{{ main6 main6 = \ ds -> case ds of _ { Box ds1 ds2 -> case ds1 main7 main_number ds2 of dt { D# ipv -> Box (\ @ dum $d(%,%) -> ds1 ($p1(%,%) $d(%,%), $p2(%,%) $d(%,%))) dt } } }}} The issue is caused by the fact that the `Box` constructor has a local tuple constraint: {{{#!hs type Numerical a = (Fractional a, Real a) data Box a = Box { func :: forall dum. (Numerical dum) => dum -> a -> a , obj :: !a } }}} When code that unpacks `Box` and uses its local constraint to do some stuff, the solver needs to produce the tuple constraint. A tuple constraint is implemented as a class with its components as superclasses. The solution with my current patch goes like: {{{ runStage interact with inerts { workitem = [W] $d(%,%) :: (Fractional num[sk], Real num[sk]) (CDictCan(psc)) updSolvedSetTcs: [W] $d(%,%) :: (Fractional num[sk], Real num[sk]) newWantedEvVar/cache hit [G] $dFractional :: Fractional num[sk] newWantedEvVar/cache hit [G] $dReal :: Real num[sk] addTcEvBind a2bg [W] $d(%,%) = C:(%,%) @[Fractional num[sk], Real num[sk]] [$dFractional, $dReal] end stage interact with inerts } }}} The old, unpatched solution goes like: {{{ runStage interact with inerts { workitem = [W] $d(%,%) :: (Fractional dum[sk], Real dum[sk]) (CDictCan(psc)) addTcEvBind a1Tk [W] $d(%,%) = $d(%,%) end stage interact with inerts } }}} The old solution just uses the tuple constraint we are given. The new solution is trying to be too smart: It tries to solve from the top-level instance and it can do so because the solver has decomposed the given tuple constraint into given constraints of its components. So we end up constructing a dictionary that is essentially the same as a given one. Bad! It's not clear to me how to exclude corner cases like this. It is potentially possible that we *do* want to try to solve a tuple constraint from instances because we might be able to find a more concrete solution to one of its components. Is it possible to notice this inefficiency in a core2core pass and resolve it then instead? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835 | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonpj: @@ -48,0 +48,3 @@ + + See also + * #5835, which will be fixed when this one is fixed. New description: Say `R` is a superclass of `MR` but only uses one of the type variables. If this type variable is fixed then we know that we are going to use a specific instance for `R`. Thus, the optimiser *could* specialise all methods from the superclass at this point leading to better code. {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} module Foo where class R t => MR t m where push :: t -> m -> Int class R t where pull :: t -> Int --type MR2 t m = (R t, MR t m) instance MR Int Int where push = max instance R Int where pull = negate myf :: (MR Int a) => a -> Int -> Int myf _ = pull }}} To give a concrete example, `R` is a super class of `MR` but only mentions the first type variable. Thus when we fix it in `myf`, we could optimise the definition to `myf _ = negate` by inlining the class method. Reid points out that if you have a definition like {{{ data X = X f :: R X => Int -> Int f = pull }}} then the instance for `R X` could be provided by another module. However it is common to structure large applications with super class constraints so it would be desirable to do better. See also * #5835, which will be fixed when this one is fixed. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835 | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Another potential instance of this spotted in the wild: `MonadBaseControl IO m => m ()`, where `MonadBaseControl b m` has indirect superclasses including `Applicative b` and `Monad b`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised.
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: danharaj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #5835 | Differential Rev(s): Phab:D2714
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Matthew Pickering

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835 | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835, #13943 | Differential Rev(s): Phab:D2714 Wiki Page: | -------------------------------------+------------------------------------- Changes (by vagarenko): * related: #5835 => #5835, #13943 Comment: It looks like this patch introduced a regression: #13943 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: danharaj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5835, #13943, | Differential Rev(s): Phab:D2714 #14434 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * related: #5835, #13943 => #5835, #13943, #14434 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12791#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12791: Superclass methods could be more aggressively specialised.
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: danharaj
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #5835, #13943, | Differential Rev(s): Phab:D2714
#14434 |
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC