
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. When the argument lists are all definitely of one type, instance selection works as expected; however, with numeric types, for example, things don't work out. I'm not sure how to express the idea that the result tuple determines the arguments types, with either of functional dependencies or associated types. -- _jsn |...example...| http://github.com/jsnx/haskell-demos/tree/master/generic_zip%2FGenericZip.hs

On Fri, 21 Nov 2008, Jason Dusek wrote:
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.
I think that the ZipList type for Applicative functors is a solution. http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Applicati...

That would solve the problem that solving the problem would solve, but it does not solve the problem I asked about! -- _jsn

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-... 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

Sean Leather wrote:
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))
Also, module Data.Zippable of package http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bff has: tryZip :: Zippable f => f a -> f b -> Either String (f (a,b)) where "Either String" plays the role of "Maybe" above. And for the underlying Zippable class, Joachim Breitner has implemented an automatic TH deriver (makeZippable) using the derive-package. So no manual boilerplate at all is necessary to use this version of generic zip. (And there is also a tryZipWith.) Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

On Friday 21 November 2008 9:40:14 am Jason Dusek wrote:
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.
When the argument lists are all definitely of one type, instance selection works as expected; however, with numeric types, for example, things don't work out. I'm not sure how to express the idea that the result tuple determines the arguments types, with either of functional dependencies or associated types.
Here's some fancy type system stuff for your viewing pleasure: ---- snip ---- {-# LANGUAGE GADTs , TypeFamilies , EmptyDataDecls , TypeOperators , ScopedTypeVariables , FlexibleContexts #-} data Nil data a ::: b infixr ::: data Tuple ts where Nil :: Tuple Nil (:::) :: t -> Tuple ts -> Tuple (t ::: ts) type family Fun ts r :: * type instance Fun Nil r = r type instance Fun (t ::: ts) r = t -> Fun ts r type family Lists ts :: * type instance Lists Nil = Nil type instance Lists (t ::: ts) = [t] ::: Lists ts class Tup ts where uncurryT :: Fun ts r -> Tuple ts -> r curryT :: (Tuple ts -> r) -> Fun ts r zipT :: Tuple (Lists ts) -> [Tuple ts] instance Tup Nil where uncurryT r Nil = r curryT f = f Nil zipT Nil = repeat Nil instance Tup ts => Tup (t ::: ts) where uncurryT f (v ::: vs) = uncurryT (f v) vs curryT f = \v -> curryT (\t -> f (v ::: t)) zipT (l ::: ls) = zipWith (:::) l (zipT ls) zipWithT :: forall ts r. (Tup ts, Tup (Lists ts)) => ts -> Fun ts r -> Fun (Lists ts) [r] zipWithT witness f = cT (\t -> map (uT f) (zipT t)) where cT :: (Tuple (Lists ts) -> [r]) -> Fun (Lists ts) [r] cT = curryT uT :: Fun ts r -> Tuple ts -> r uT = uncurryT zwp :: forall a. Num a => [a] -> [a] -> [a] -> [a] zwp = zipWithT (undefined :: a ::: a ::: a ::: Nil) (\x y z -> x + y + z) zwf :: forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] zwf = zipWithT (undefined :: a ::: b ::: c ::: Nil) ---- snip ---- You'll need a GHC that's 6.10-ish for this to work. Cheers, -- Dan
participants (5)
-
Dan Doel
-
Henning Thielemann
-
Janis Voigtlaender
-
Jason Dusek
-
Sean Leather