Fellow Haskellers,

Please forgive my lack of brevity here.

It has always seemed to me that having multiple zip functions with
different names (zip, zip3, zip4, etc..) was unfortunate, and a single
zip that handled all possible tuples would be better.  Now, with
Multi-Parameter Type Classes and Functional Dependencies, we have an
opportunity to make zip more sensible.

Note: I am not proposing this as a "typo" for the current report, but
for a future version of standard Haskell.  Obviously, this would only be
valid if MPTC's and FD's become part of the future standard.

I would propose:
   o  zip be renamed to zip2 and zipWith to zipWith2
   o  zip be changed to map tuples-of-lists to lists-of-tuples (the
"opposite" of unzip)
   o  A Zippable class be created, defining zip and unzip for all tuple
types (or at least the first few)
   o  (optional) a ZipFunctor class (subclass of Functor) defining a
function which applies a collection of functions to a collection of
values giving a collection of results.  The list type ([]) would of
course be a member of this class.

The advantages I see:
   o  zip . unzip === id
   o  types of zip & unzip are consistent with each other
   o  zip could be extended via the class mechanism to work with
non-list collections, and non-tuple elements

Disadvantages:
   o  Existing code using zip would break
   o  Implementation might be less efficient than current zip & unzip

Sample implementation:
> module Zip (zip, unzip, Zippable, ZipFunctor, zip2, zip3, zip4, zipWith2, zipWith3, 
>zipWith4) where
> import Prelude hiding (zip, unzip, zipWith3, zip3)
> 
> class (Functor f) => ZipFunctor f where
>    ($$) :: f (a->b) -> f a -> f b
> 
> instance ZipFunctor [] where
>    (f:fs) $$ (x:xs) = (f x):(fs $$ xs)
>    _ $$ _ = []
> 
> zipWith2 :: (ZipFunctor f) => (a->b->c) -> f a -> f b -> f c
> zipWith2 f xs ys = f `fmap` xs $$ ys
> 
> zipWith3 :: (ZipFunctor f) => (a->b->c->d) -> f a -> f b -> f c -> f d
> zipWith3 f xs ys zs = f `fmap` xs $$ ys $$ zs
> 
> zipWith4 :: (ZipFunctor f) => (a->b->c->d->e) -> f a -> f b -> f c -> f d -> f e
> zipWith4 f xs1 xs2 xs3 xs4 = f `fmap` xs1 $$ xs2 $$ xs3 $$ xs4
> 
> zip2 :: ZipFunctor f => f a -> f b -> f (a,b)
> zip2 = zipWith2 (,)
> zip3 :: ZipFunctor f => f a -> f b -> f c -> f (a,b,c)
> zip3 = zipWith3 (,,)
> zip4 :: ZipFunctor f => f a -> f b -> f c -> f d -> f (a,b,c,d)
> zip4 = zipWith4 (,,,)
> 
> class Zippable a f b | a -> f b, f b -> a where
>    zip :: a -> f b
>    unzip :: f b -> a
> 
> instance (ZipFunctor f) => Zippable (f a,f b) f (a,b) where
>    zip (xs,ys) = zip2 xs ys
>    unzip xys = (fmap fst xys, fmap snd xys)
> 
> instance (ZipFunctor f) => Zippable (f a,f b,f c) f (a,b,c) where
>    zip (xs,ys,zs) = zip3 xs ys zs
>    unzip xyzs = ( fmap (\(x,_,_)->x) xyzs,
>                   fmap (\(_,y,_)->y) xyzs,
>                   fmap (\(_,_,z)->z) xyzs  )
> 
> instance (ZipFunctor f) => Zippable (f a,f b,f c,f d) f (a,b,c,d) where
>    zip (xs1,xs2,xs3,xs4) = zip4 xs1 xs2 xs3 xs4
>    unzip xs = ( fmap (\(x,_,_,_)->x) xs,
>                 fmap (\(_,x,_,_)->x) xs,
>                 fmap (\(_,_,x,_)->x) xs,
>                 fmap (\(_,_,_,x)->x) xs  )


Question: is there a problem with defining unzip in terms of fmap, as
opposed to the current definition in the prelude, which uses foldr?

Best regards,
Matt Harden

Reply via email to