[Haskell-cafe] varargs zip

Sean Leather leather at cs.uu.nl
Fri Nov 21 11:22:24 EST 2008


>  It came up on IRC last night that there is no "generic" zip in
>  Haskell. I decided to write one as an example, but it only
>  half works.
>

That depends on how you define "generic." ;)

EMGM [1] has a generic zipWith [2]:

> zipWith :: FRep3 ZipWith f => (a -> b -> c) -> f a -> f b -> Maybe (f c)

This is generic according to the container type 'f'. A particular
specialization of this is zip:

> zip :: FRep3 ZipWith f => f a -> f b -> Maybe (f (a, b))

[1] http://www.cs.uu.nl/wiki/GenericProgramming/EMGM
[2]
http://hackage.haskell.org/packages/archive/emgm/0.1/doc/html/Generics-EMGM-Functions-ZipWith.html

http://github.com/jsnx/haskell-demos/tree/master/generic_zip%2FGenericZip.hs


>From looking at your code, it appears that you want a zip that is generic
according to arity. You also don't seem to care about the container type,
since you have only lists. So, the above isn't really related.

Here's an adaptation of your code that works. Personally, I'd probably use
Template Haskell. This is not really generic at all. Rather it's an
advertisement for overloading. ;)

> {-# LANGUAGE FlexibleInstances #-}

> module GenericZip where

> import Prelude hiding (zip)
> import qualified Prelude (zip)

> class Zip f where
>   zip :: f

> instance Zip ([a] -> [a]) where
>   zip = id

> instance Zip ([a] -> [b] -> [(a, b)]) where
>   zip = Prelude.zip

> instance Zip ([a] -> [b] -> [c] -> [(a, b, c)]) where
>   zip as bs cs = zipWith (\a (b,c) -> (a,b,c)) as $ zip bs cs

> instance Zip ([a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]) where
>   zip as bs cs ds = zipWith (\a (b,c,d) -> (a,b,c,d)) as $ zip bs cs ds

> example = zip [1,2::Int] ['a','b'] ["1","b"] :: [(Int,Char,String)]

Regards,
Sean
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081121/f5570e20/attachment.htm


More information about the Haskell-Cafe mailing list