An attempt at foldr/build fusion for zip

Matt Harden matth@mindspring.com
Sun, 22 Apr 2001 08:45:45 -0500


Hi,

I think I may have found a way to get zip & friends to fuse with *both*
of their input lists.  I am not a heavy ghc hacker, though, so I may be
missing something important that makes this unworkable.  I have no idea
what kind of code this would actually end up creating.

Anyway, here's my attempt; it ties in with the current foldr2 scheme.  I
eagerly any await comments or questions, especially from the foldr/build
gurus.

-- foldr2_both.lhs:
Attempting to fuse zip with both input lists.
We seem to be forced to use a recursive datatype to accomplish this.
We're using newtype, so there should be no overhead from
construction/deconstruction of this type, right?

\begin{code}
newtype BuildZip a b = BZ ((a -> (BuildZip a b) -> b) -> b)

bz :: (forall b. (a->b->b)->b->b) -> b -> BuildZip a b
bz f n = f (\x xs -> BZ (\c -> c x xs)) (BZ (\_ -> n))
{-# INLINE bz #-}

foldr2_both :: (a->b->c->c) -> BuildZip a c -> BuildZip b c -> c
foldr2_both k (BZ xs) (BZ ys) =
       xs (\x xs' ->
       ys (\y ys' ->
           k x y (foldr2_both k xs' ys')
       ) )

{-# RULES
"foldr2/both"   forall k n (f::forall z.(a->z->z)->z->z)
                           (g::forall z.(b->z->z)->z->z) .
                  foldr2 k n (build f) (build g) =
                    foldr2_both k (bz f n) (bz g n)
 #-}
\end{code}
-- END foldr2_both.lhs

Best regards,
Matt Harden