Re: [GHC] #7206: Implement cheap build

#7206: Implement cheap build -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.4.2 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 bgamari): I took another look at this while waiting for a build and I believe I have identified the source of the additional allocations. In particular I looked at the `real/parser` nofib case, which regresses in allocations by about 3% when using `cheapBuild` for `unpack`, {{{ "unpack" [~1] forall a . unpackCString# a = cheapBuild (unpackFoldrCString# a) }}} The issue is replicated with an example as simple as, {{{#!hs module Hi where data Pat = PatVar Id | PatCon Id [Pat] | PatWild | PatTuple [Pat] deriving (Show{-was:Text-}) type Id = String }}} A pattern which occurs quite often in `parser`. Let's consider the code generated for the `PatTuple` branch of `$cshowsPrec` (taken from the output of the phase 1 simplifier pass), {{{#!hs -- Before cheapBuild PatTuple b1 -> case a of { GHC.Types.I# x -> case GHC.Prim.tagToEnum# @ Bool (GHC.Prim.>=# x 11#) of { False -> ++ @ Char lvl (GHC.Show.showList__ @ Pat $cshowList b1 eta); True -> GHC.Types.: @ Char GHC.Show.shows6 (++ @ Char lvl (GHC.Show.showList__ @ Pat $cshowList b1 (GHC.Types.: @ Char GHC.Show.shows4 eta))) } } -- After cheapBuild PatTuple b1 -> let { p :: ShowS p = \ (x :: String) -> GHC.CString.unpackAppendCString# "PatTuple "# (GHC.Show.showList__ @ Pat $cshowList b1 x) } in case a of { GHC.Types.I# x -> case GHC.Prim.tagToEnum# @ Bool (GHC.Prim.>=# x 11#) of { False -> p eta; True -> GHC.Types.: @ Char GHC.Show.shows6 (p (GHC.Types.: @ Char GHC.Show.shows4 eta)) } } }}} We see that after the introduction of `cheapBuild` the `p` binding is no longer inlined. Comparing the output of `dump-inlinings` reveals why, **Before `cheapBuild`** {{{ Considering inlining: p arg infos [ValueArg] interesting continuation BoringCtxt some_benefit True is exp: True is work-free: True guidance IF_ARGS [0] 80 0 discounted size = 60 ANSWER = YES Inlining done: p Inlined fn: \ (x :: GHC.Base.String) -> GHC.Base.++ @ GHC.Types.Char lvl (GHC.Types.: @ GHC.Types.Char GHC.Show.shows5 (GHC.Show.showLitString b1 (GHC.Types.: @ GHC.Types.Char GHC.Show.shows5 x))) Cont: ApplyToVal nodup (GHC.Types.: @ GHC.Types.Char GHC.Show.shows4 x) Stop[BoringCtxt] [GHC.Types.Char] }}} **After `cheapBuild`** {{{ Considering inlining: p arg infos [ValueArg] interesting continuation BoringCtxt some_benefit True is exp: True is work-free: True guidance IF_ARGS [0] 110 0 discounted size = 90 ANSWER = NO }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/7206#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC