[Haskell-cafe] Rewrite rules for enumFromTo

Joachim Breitner mail at joachim-breitner.de
Thu Apr 19 10:47:51 CEST 2012


Hi Michael,

Am Mittwoch, den 18.04.2012, 19:21 +0300 schrieb Michael Snoyman:
> I'm quite a novice at rewrite rules; can anyone recommend an approach
> to get my rule to fire first?

I’m not an expert of rewrite rules either, but from some experimentation
and reading -dverbose-core2core (which is not a very nice presentation,
unfortunately), I think that one reason why your rules won’t fire is
that yieldMany is inlined too early. 

diff --git a/conduit/Data/Conduit/Internal.hs b/conduit/Data/Conduit/Internal.hs
index bf2de63..8050c2c 100644
--- a/conduit/Data/Conduit/Internal.hs
+++ b/conduit/Data/Conduit/Internal.hs
@@ -353,7 +353,7 @@ yieldMany =
   where
     go [] = Done Nothing ()
     go (o:os) = HaveOutput (go os) (return ()) o
-{-# INLINE yieldMany #-}
+{-# INLINE [1] yieldMany #-}
 
 {-# RULES
     "yield/bind" forall o (p :: Pipe i o m r). yield o >> p = yieldBind o p

changes that.

It might be hard to actually match on [1...1000], as that is very early
replaced by the specific instance method which then takes part in the
foldr/build-rewrite-reign. But maybe instead of specializing enumFromTo,
you already get good and more general results in hooking into that?
Juding from the code, you are already trying to do so, as you have a
yieldMany/build rule that fires with above change:

$ cat Test.hs 
module Test where

import Data.Conduit
import qualified Data.Conduit.List as CL

x :: Pipe i Integer IO ()
x = mapM_ yield [1..1000]

$ ghc -O -fforce-recomp -ddump-rule-firings Test.hs 
[1 of 1] Compiling Test             ( Test.hs, Test.o )
Rule fired: Class op enumFromTo
Rule fired: mapM_ yield
Rule fired: yieldMany/build

Oh, and as you can see, you don’t have to export the functions ocurring
in the rules, as you did with yieldMany and yieldBuild.

I don’t know conduits well, but you should check whether this also
affects you:
http://www.haskell.org/pipermail/haskell-cafe/2011-October/095985.html
If conduits are constructed like in steam fusion, the build rule might
not be of any use. 

Greetings,
Joachim

-- 
Joachim "nomeata" Breitner
  mail at joachim-breitner.de  |  nomeata at debian.org  |  GPG: 0x4743206C
  xmpp: nomeata at joachim-breitner.de | http://www.joachim-breitner.de/

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120419/859e02b9/attachment.pgp>


More information about the Haskell-Cafe mailing list