Hi,

there's quite some material on how to debug/track rewrite rules that
do fire. However, I couldn't find information about how to find out
what is wrong with a rule that supposedly should, but actually doesn't
fire. Concretely, I would like to add a rewrite rule that converts

  mconcat . map (fromWrite w)

to

  fromWriteList w

The relevant definitions and types are:

mconcat = foldr append empty
append           :: Builder -> Builder -> Builder
empty            :: Builder
fromWrite       :: Write a -> a -> Builder
fromWriteList  :: Write a -> [a] -> Builder

The rewrite rule that I tried is

"foldr/fromWrite" forall w.
     foldr (\x b -> append (fromWrite w x) b) empty = fromWriteList w

combined with {-# INLINE [1] #-} anotations on the `append`, `empty`,
`fromWrite` and `fromWriteList`. However, the rule doesn't fire for a
definition like

word8s :: [Word8] -> Builder
word8s = mconcat . map (fromWrite writeWord8)

I suspect that the foldr/build fusion rules are interacting. However,
I don't know how this interaction looks like. Is there a way to track
all simplifications of `word8s` in all phases? If there was, then I
could formulate my rule such that it is reduced with respect to the
other rewriting rules. Then, the interaction should work out.

thanks for your help,
Simon

PS: The above definitions are part of the builder for the bytestring
package [1] and my experiment on rule firings can be found here [2].

[1] https://github.com/meiersi/bytestring
[2] 
https://github.com/meiersi/bytestring/blob/master/tests/builder/WriteListFusion.hs

_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to