[Haskell-cafe] Why is there no Zippable class? Would this work?

Jeff Heard jefferson.r.heard at gmail.com
Thu Jul 16 18:02:58 EDT 2009


Beautiful.  Can we have a version on hackage?

On Thu, Jul 16, 2009 at 5:56 PM, Job Vranish<jvranish at gmail.com> wrote:
> I was needing a way to zip generic data structures together today and was
> very annoyed to find that there is no Zippable class, or variant there of.
>
> So I made my own:
>
> class (Foldable f, Functor f) => Zippable f where
>   fmaps :: (Foldable g) => g (a -> b) -> f a -> f b
>   fmaps' :: [a -> b] -> f a -> f b -- to save a step on instance
> implementation
>   zipWith :: (a -> b -> c) -> f a -> f b -> f c
>   zip ::  f a -> f b -> f (a, b)
>   unzip :: f (a, b) -> (f a, f b)
>
>   fmaps fs a = fmaps' (toList fs) a
>   fmaps' fs a = fmaps fs a
>   zipWith f a b = fmaps (fmap f a) b
>   zip = zipWith (,)
>   unzip a = (fmap fst a, fmap snd a)
>
> instance Zippable [] where
>   fmaps' (fx:fs) (x:xs) = fx x : fmaps' fs xs
>   fmaps' _       _      = []
>
> --The fmaps function is also quite handy as a replacment for zipWith3,
> zipWith4, etc...
> --For example:
>
> x = [1, 3, 5, 7, 3]
> y = [6, 9, 3, 1, 4]
> z = [2, 4, 0, 8, 2]
> test = fmap (,,) x `fmaps` y `fmaps` z
> -- > [(1,6,2),(3,9,4),(5,3,0),(7,1,8),(3,4,2)]
>
> --you can also throw in a functor instance to remove the dependency on the
> Functor class, but it
> --  might not be worth it:
> instance (Zippable f) => Functor f where
>   fmap f a = fmaps (repeat f) a
>
>
> Is there any good reason that there isn't something like this in the
> standard libraries? Or, as far as I can tell, on hackage?
> If not, then maybe I'll stick it on hackage.
>
> - Job Vranish
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list