[GHC] #10012: Cheap-to-compute values aren't pushed into case branches inducing unnecessary register pressure

GHC ghc-devs at haskell.org
Fri Apr 22 08:48:11 UTC 2016


#10012: Cheap-to-compute values aren't pushed into case branches inducing
unnecessary register pressure
-------------------------------------+-------------------------------------
        Reporter:  bgamari           |                Owner:  bgamari
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.8.4
      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 was thinking about this a bit more recently; to recap, the issue here is
 that GHC is unwilling to push bindings into case analyses when this would
 imply duplication. This leaves GHC no other option but to allocate the
 shared binding on the heap.

 To see an example of this let's look at `bytestring`'s `Builder`. The key
 branch here is `Data.ByteString.Builder.Internal.ensureFree`,
 {{{#!hs
 -- | The result of a build action
 data BuildSignal a =
     -- | We wrote all of the content we were asked to
     Done !(Ptr Word8) a
     -- | The buffer we were provided is full, but here's a continuation
     -- BuildStep to pick up where we left off
   | BufferFull !Int !(Ptr Word8) (BuildStep a)

 newtype Builder = Builder (forall r. BuildStep r -> BuildStep r)
 instance Monoid Builder where ...
 type BuildStep a = BufferRange -> IO (BuildSignal a)

 ensureFree :: Int -> Builder
 ensureFree minFree =
     builder step
   where
     step :: BuildStep r -> BuildStep r
     step k br@(BufferRange op ope) =
       | ope `minusPtr` op < minFree  -> return $ bufferFull minFree op k
       | otherwise                    -> k br
 }}}
 The idea here is that we are filling a pre-allocated buffer (described by
 the `BufferRange`) with bytes; `ensureFree` verifies that the buffer has
 at least `minFree` free bytes remaining.

 The trouble comes when we write something like,
 {{{#!hs
 twoWord64s :: Word64 -> Word64 -> Builder
 twoWord64s a b = word64 (f a) <> word64 (f b)
   where
     -- just some cheap to evaluate function that we really don't want
     -- to build a thunk for
     f = (+1)
 }}}
 which in STG turns into something like,
 {{{#!hs
 twoWord64s' :: Word64 -> Word64
             -> forall r. BuildStep r -> BufferRange -> IO (BuildSignal r)
 twoWord64s' a b cont br =
     let fa, fb :: Word64
         fa = a + 1
         fb = b + 1
     in case br of
          BufferRange op ope ->
            case ope `minusPtr` op < minFree  of
              True  -> return $ bufferFull 16 {- bytes -} op cont
              False -> cont br
 }}}

 It seems that one interesting (albeit slightly inelegant) way to
 addressing this issue is to provide a means for the library author to
 indicate that a given `case` should be considered "cheap" to push through.
 That is, you might define `ensureFree` as,
 {{{#!hs
 ensureFree :: Int -> Builder
 ensureFree minFree =
     builder step
   where
     step k br@(BufferRange op ope) =
       case ope `minusPtr` op < minFree of
         True    -> return $ bufferFull minFree op k
         False   -> k br
       {-# INLINE_THROUGH #-}
       -- Telling GHC "it's okay if we lose sharing across
       -- the branches of this case, I would far prefer code duplication
       -- to allocation"
 }}}

 I don't believe there are too many places where this sort of pragma would
 be useful, but when it is needed I suspect it would be very useful indeed.

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


More information about the ghc-tickets mailing list