[GHC] #11688: Bytestring break failing rewrite to breakByte and failing to eliminate boxing/unboxing
GHC
ghc-devs at haskell.org
Tue Mar 8 10:02:31 UTC 2016
#11688: Bytestring break failing rewrite to breakByte and failing to eliminate
boxing/unboxing
-------------------------------------+-------------------------------------
Reporter: alexbiehl | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
I briefly looked at this; I left a comment on the `bytestring` ticket
which I'll reproduce here,
> I suspect the issue here is that `(==)` is being inlined too early,
hiding the rule fire opportunity. By contrast, if you give `(==)` another
name with a later inline pragma the `break -> breakByte` rule fires as
expected.
>
> {{{#!hs
> main = do
> chunk <- DB.hGetSome stdin 32768
> let newline = c2w '\n'
> let (prefix,suffix) = DB.break (eq newline) chunk
> DB.hPut stdout prefix
> DB.hPut stdout suffix
>
> eq :: Eq a => a -> a -> Bool
> eq = (==)
> {-# INLINE [1] eq #-}
>
> {-# RULES
> "ByteString specialise break (eq x)" forall x.
> DB.break (eq x) = DB.breakByte x
> #-}
> }}}
>
> Actually, even if one doesn't specify an explicit phase on `eq` the rule
still fires! This is likely accidental, since GHC just happens to look at
the `breakByte` rule before the `eq` inlining.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11688#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list