[GHC] #14790: eqTypeRep does not inline
GHC
ghc-devs at haskell.org
Sun Feb 11 17:13:56 UTC 2018
#14790: eqTypeRep does not inline
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.1-alpha2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by dfeuer):
mpickering, I get a bunch of things that look like this:
{{{#!hs
Considering inlining: eqTypeRep
arg infos [TrivArg, TrivArg]
interesting continuation CaseCtxt
some_benefit True
is exp: True
is work-free: True
guidance IF_ARGS [52 128] 210 0
discounted size = 180
ANSWER = NO
}}}
The continuation, some_benefit, and work-free lines all look good. I don't
know how to read the guidance line. Has GHC allowed `eqTypeRep` to get too
large to inline in most cases? If its decisions seem reasonable to you and
other experienced folks, perhaps we should do something like
{{{#!hs
typeRepsSame :: forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Bool
typeRepsSame a b = typeRepFingerprint a == typeRepFingerprint b
eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
eqTypeRep a b
| typeRepsSame a b = Just (unsafeCoerce# HRefl)
| otherwise = Nothing
{-# INLINE eqTypeRep #-}
}}}
inlining a very thin wrapper, but I was surprised enough by the choice
that I figured it might point to a more general inlining heuristic
problem.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14790#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list