In GHC's Control.Arrow implementation, there are several rewrite rules
which exploit some properties of arrows.  For example,

"compose/arr" forall f g . arr f >>> arr g = arr (f >>> g)
"first/arr"   forall f . first (arr f) = arr (first f)
"second/arr"  forall f . second (arr f) = arr (second f)

... and so forth.

Now say I have a simple arrow instance:

newtype SF a b = SF ([a] -> [b])

instance Arrow SF where
   arr f = SF (map f)

   first (SF f) = SF g
      where g l = let (x, y) = unzip l
                   in zip (f x) y

   (SF f) >>> (SF g) = SF (g . f)

and some arrow composition:

foo :: SF (Int,Int) (Int,Int)
foo = first (arr (+1)) >>> first (arr (+2) >>> arr (+3))

I was expecting that ghc would at least make use of compose/arr or
even first/arr, but it didn't appear to be the case.  I was using
ghc-6.6, and -ddump-simpl-stats showed a bunch of list-specific rules
were fired (map, mapFB, fold/build, etc), but I did not see any
arrow-related rules being applied.

Were the rewrite rules subsumed by inlining or beta-reduction?  Am I
missing something here?

Thanks,
Eric
_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to