[commit: ghc] master: Use top-level instances to solve superclasses where possible (748b797)

git at git.haskell.org git at git.haskell.org
Tue Jan 31 23:00:27 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/748b79741652028827b6225c36b8ab55d22bdeb0/ghc

>---------------------------------------------------------------

commit 748b79741652028827b6225c36b8ab55d22bdeb0
Author: Daniel Haraj <dan at obsidian.systems>
Date:   Tue Jan 31 22:28:55 2017 +0000

    Use top-level instances to solve superclasses where possible
    
    This patch introduces a new flag `-fsolve-constant-dicts` which makes the
    constraint solver solve super class constraints with available dictionaries if
    possible. The flag is enabled by `-O1`.
    
    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:
    
    ```
    {-# 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, notice that we get the instance for `Num Int` by
    using the class selector `p1`.
    
    ```
    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, nicely optimised code!
    
    ```
    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#)
        }
    ```
    
    Reviewers: simonpj, bgamari, austin
    
    Reviewed By: simonpj
    
    Subscribers: mpickering, rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D2714
    
    GHC Trac Issues: #12791, #5835


>---------------------------------------------------------------

748b79741652028827b6225c36b8ab55d22bdeb0
 compiler/main/DynFlags.hs                     |   3 +
 compiler/typecheck/TcInteract.hs              | 259 ++++++++++++++++++++++++--
 compiler/typecheck/TcSMonad.hs                |  16 +-
 docs/users_guide/8.2.1-notes.rst              |   9 +
 docs/users_guide/using-optimisation.rst       |  31 +++
 testsuite/tests/perf/should_run/T12791.hs     |  15 ++
 testsuite/tests/perf/should_run/T12791.stdout |   1 +
 testsuite/tests/perf/should_run/T5835.hs      |  11 ++
 testsuite/tests/perf/should_run/T5835.stdout  |   1 +
 testsuite/tests/perf/should_run/all.T         |  20 ++
 10 files changed, 351 insertions(+), 15 deletions(-)

Diff suppressed because of size. To see it, use:

    git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 748b79741652028827b6225c36b8ab55d22bdeb0


More information about the ghc-commits mailing list