[GHC] #11701: ghc generates significant slower code

GHC ghc-devs at haskell.org
Mon Mar 14 09:31:22 UTC 2016


#11701: ghc generates significant slower code
-------------------------------------+-------------------------------------
        Reporter:  HuStmpHrrr        |                Owner:
            Type:  bug               |               Status:  patch
        Priority:  normal            |            Milestone:  8.0.1
       Component:  Compiler          |              Version:  7.10.3
      Resolution:                    |             Keywords:  efficiency
Operating System:  Linux             |         Architecture:  x86_64
 Type of failure:  Runtime           |  (amd64)
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):  Phab:D1997
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 A factor of 5 is an impressively big loss from failing to inline `even`!

 I think we should investigate why it ''isn't'' being inlined
 automatically.  I tried a tiny case:
 {{{
 module Foo where
   even       :: (Integral a) => a -> Bool
   even n          =  n `rem` 2 == 0


 module Bar where
   import Foo
   f :: Int -> Bool
   f x = Foo.even x
 }}}
 Sure enough, `even` is not inlined.  With `-dverbose-core2core -ddump-
 inlinings` we get
 {{{
 Considering inlining: even
   arg infos [ValueArg, TrivArg]
   interesting continuation BoringCtxt
   some_benefit True
   is exp: True
   is work-free: True
   guidance IF_ARGS [60 0] 240 0
   discounted size = 120
   ANSWER = NO
 }}}
 So we are only getting a tiny discount from the fact that we are giving a
 completely fixed dictionary to `even`; even though `even`'s body is
 dominated by dictionary selections that would disappear if we inlined
 `even`.

 So maybe we should look at our discounting scheme.  See
 `CoreUnfold.classOpSize` and `ufDictDiscount` in particular.

 But there's a bit more to it than that. Here's the unfolding for `even`:
 {{{
      Unfolding: (\ @ a ($dIntegral :: Integral a) (eta :: a) ->
                  let {
                    $dReal :: Real a = $p1Integral @ a $dIntegral
                  } in
                  let {
                    $dNum :: Num a = $p1Real @ a $dReal
                  } in
                  ==
                    @ a
                    ($p1Ord @ a ($p2Real @ a $dReal))
                    (rem @ a $dIntegral eta (fromInteger @ a $dNum even2))
                    (fromInteger @ a $dNum even1)) -}
 }}}
 The original argument is `$dIntegral` and only two of the seven
 dictionary-selection operations are applied to that argument; and only
 they attract discounts.

 Food for thought here.  This function ''obviously'' should be inlined
 (when applied to a particular fixed dictionary) but it's not quite clear
 how to make that happen.

 Making it INLINEABLE, as the patch does, makes it specialisable which is
 good. Then it becomes small, and then it gets inlined.  That path works
 quite well.  Maybe all overloaded functions, perhaps up to some size
 limit, should automatically be INLINEABLE.

 Food for thought

 Simon

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11701#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list