
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