
Hello, I seems to us (my friends and me) that term rewriting rules for ByteString are not fired in recent GHCs. 6.12.3 OK 7.0.4 NG 7.4.1 NG 7.6.1RC1 NG For example, with the example from this ticket http://hackage.haskell.org/trac/ghc/ticket/3703 results in as follows: % ghc -O -ddump-simpl-stats --make breakOn.hs 14 RuleFired 4 Class op showsPrec 2 Class op show 2 eqChar#->case 2 unpack 2 unpack-list 1 Class op == 1 Class op >> There is no ByteString rules. Is this a bug or intention? --Kazu {-# LANGUAGE OverloadedStrings #-} import qualified Data.ByteString.Char8 as B main :: IO () main = do let string1 = B.pack "This is a string" string2 = B.pack "This is another string" print (breakOn ' ' string1) print (breakOn ' ' string2) breakOn :: Char -> B.ByteString -> (B.ByteString, B.ByteString) breakOn c = B.break (c==)

Another data point:
The bytestring 'break' rule fired fine for me (GHC 7.4.1 Linux x86-64).
On Mon, Aug 27, 2012 at 9:37 PM, Kazu Yamamoto
Hello,
I seems to us (my friends and me) that term rewriting rules for ByteString are not fired in recent GHCs.
6.12.3 OK 7.0.4 NG 7.4.1 NG 7.6.1RC1 NG
For example, with the example from this ticket http://hackage.haskell.org/trac/ghc/ticket/3703 results in as follows:
% ghc -O -ddump-simpl-stats --make breakOn.hs 14 RuleFired 4 Class op showsPrec 2 Class op show 2 eqChar#->case 2 unpack 2 unpack-list 1 Class op == 1 Class op >>
There is no ByteString rules.
Is this a bug or intention?
--Kazu
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.ByteString.Char8 as B
main :: IO () main = do let string1 = B.pack "This is a string" string2 = B.pack "This is another string" print (breakOn ' ' string1) print (breakOn ' ' string2)
breakOn :: Char -> B.ByteString -> (B.ByteString, B.ByteString) breakOn c = B.break (c==)
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Hi Kazu, On Tue, Aug 28, 2012 at 01:37:32PM +0900, Kazu Yamamoto wrote:
I seems to us (my friends and me) that term rewriting rules for ByteString are not fired in recent GHCs.
Thanks for the report. I've filed a ticket here: http://hackage.haskell.org/trac/ghc/ticket/7374 Thanks Ian
participants (3)
-
Ian Lynagh
-
Kazu Yamamoto
-
Thomas DuBuisson