
#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