Why is there no Zippable class? Would this work?

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

I think there are some basic equivalents in the TypeCompose and category-extras packages, for the record, but a standalone version wouldn't hurt either! - Jake

Beautiful. Can we have a version on hackage?
On Thu, Jul 16, 2009 at 5:56 PM, Job Vranish
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

After rereading page 2 of McBride and Paterson's Functional Pearl, "Applicative programming with effects", I think you are just reinventing Control.Applicative. The problem is that the default Applicative instance for [] is wrong, being a direct product rather than a direct sum. If [] were not already an instance of Applicative, you could easily define it as: import Control.Applicative data MyList a = Nil | (:::) a (MyList a) deriving (Read,Show,Eq,Ord) infixr 5 ::: -- same as [] instance Functor MyList where fmap f Nil = Nil fmap f (x ::: xs) = f x ::: fmap f xs -- different from [], sum rather than product instance Applicative MyList where pure x = x ::: Nil (<*>) (f ::: fs) (x ::: xs) = f x ::: (fs <*> xs) (<*>) _ _ = Nil x = (1::Int) ::: 3 ::: 5 ::: 7 ::: 3 ::: Nil y = (6::Int) ::: 9 ::: 3 ::: 1 ::: 4 ::: Nil z = (2::Int) ::: 4 ::: 0 ::: 8 ::: 2 ::: Nil test = (,,) <$> x <*> y <*> z
test (:::) (1,6,2) ((:::) (3,9,4) ((:::) (5,3,0) ((:::) (7,1,8) ((:::) (3,4,2) Nil))))
Alternately, you could write a newtype for [] and give it the zippy instance for Applicative. Job Vranish 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

(I'm going to play fast and loose with constructors for this post,
treating MyList and ZipList as if they were [])
On Thu, Jul 16, 2009 at 4:10 PM, Dan Weston
-- different from [], sum rather than product instance Applicative MyList where pure x = x ::: Nil (<*>) (f ::: fs) (x ::: xs) = f x ::: (fs <*> xs) (<*>) _ _ = Nil
Unfortunately, this instance doesn't fulfill this Applicative law: pure id <*> f = f pure id <*> [1,2,3] = [id] <*> [1,2,3] = [id 1] = [1] Fortunately, the solution already exists in Control.Applicative:
-- | Lists, but with an 'Applicative' functor based on zipping, so that -- -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@ -- newtype ZipList a = ZipList { getZipList :: [a] }
instance Functor ZipList where fmap f (ZipList xs) = ZipList (map f xs)
instance Applicative ZipList where pure x = ZipList (repeat x) ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
In this case: pure id <*> [1,2,3] = [id, id, ...] <*> [1,2,3] = [id 1, id 2, id 3] = [1,2,3] -- ryan

Way cool. I have gained newfound respect for what I don't know. :) Can there ever be more than one (observably different) valid definition of pure for a given <*> that obeys all the laws? I would imagine that there could be at most one. Dan Ryan Ingram wrote:
(I'm going to play fast and loose with constructors for this post, treating MyList and ZipList as if they were [])
On Thu, Jul 16, 2009 at 4:10 PM, Dan Weston
wrote: -- different from [], sum rather than product instance Applicative MyList where pure x = x ::: Nil (<*>) (f ::: fs) (x ::: xs) = f x ::: (fs <*> xs) (<*>) _ _ = Nil
Unfortunately, this instance doesn't fulfill this Applicative law: pure id <*> f = f
pure id <*> [1,2,3] = [id] <*> [1,2,3] = [id 1] = [1]
Fortunately, the solution already exists in Control.Applicative:
-- | Lists, but with an 'Applicative' functor based on zipping, so that -- -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@ -- newtype ZipList a = ZipList { getZipList :: [a] }
instance Functor ZipList where fmap f (ZipList xs) = ZipList (map f xs)
instance Applicative ZipList where pure x = ZipList (repeat x) ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
In this case:
pure id <*> [1,2,3] = [id, id, ...] <*> [1,2,3] = [id 1, id 2, id 3] = [1,2,3]
-- ryan

Yeah I tried applicative, but saw that the <*> operator didn't do what I
want with lists, and started looking elsewhere.
I didn't even see the ZipList! Actually the other problem is that the data
structure that I'm using won't support pure, so no Applicative :(
Though for a generic zip, Applicative may be the better general purpose way
to go.
I didn't see TypeCompose and category-extras either those look pretty sweet
:)
Those would have worked. But I think I in my case, my version is a bit more
general.
Thanks for the input!
It has been very enlightening. :)
Hmmm I also should have pulled the zips out of the typeclass:
class (Foldable 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
fmaps fs a = fmaps' (toList fs) a
fmaps' fs a = fmaps fs a
zipWith :: (Zippable f) => (a -> b -> c) -> f a -> f b -> f c
zipWith f a b = fmaps (fmap f a) b
zip :: (Zippable f) => f a -> f b -> f (a, b)
zip a b = zipWith (,) a b
unzip :: (Functor f) => f (a, b) -> (f a, f b)
unzip a = (fmap fst a, fmap snd a)
instance Zippable [] where
fmaps' (fx:fs) (x:xs) = fx x : fmaps' fs xs
fmaps' _ _ = []
On Thu, Jul 16, 2009 at 8:40 PM, Ryan Ingram
(I'm going to play fast and loose with constructors for this post, treating MyList and ZipList as if they were [])
On Thu, Jul 16, 2009 at 4:10 PM, Dan Weston
wrote: -- different from [], sum rather than product instance Applicative MyList where pure x = x ::: Nil (<*>) (f ::: fs) (x ::: xs) = f x ::: (fs <*> xs) (<*>) _ _ = Nil
Unfortunately, this instance doesn't fulfill this Applicative law: pure id <*> f = f
pure id <*> [1,2,3] = [id] <*> [1,2,3] = [id 1] = [1]
Fortunately, the solution already exists in Control.Applicative:
-- | Lists, but with an 'Applicative' functor based on zipping, so that -- -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@ -- newtype ZipList a = ZipList { getZipList :: [a] }
instance Functor ZipList where fmap f (ZipList xs) = ZipList (map f xs)
instance Applicative ZipList where pure x = ZipList (repeat x) ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
In this case:
pure id <*> [1,2,3] = [id, id, ...] <*> [1,2,3] = [id 1, id 2, id 3] = [1,2,3]
-- ryan

Why is there no Zippable class? There is. You can use Data.Zippable from http://hackage.haskell.org/package/bff. It gives you a function tryZip :: Zippable k => k a -> k b -> Either String (k (a,b)) The Either in the return type is to capture an error message in case the two structures are not of the same shape. For example, for data Tree a = Leaf a | Node (Tree a) (Tree a) you would have: instance Zippable Tree where tryZip (Leaf a) (Leaf b) = Right (Leaf (a,b)) tryZip (Node a1 a2) (Node b1 b2) = do z1 <- tryZip a1 b1 z2 <- tryZip a2 b2 return (Node z1 z2) tryZip _ _ = Left "Structure mismatch." Of course, you can get an "unsafe" zip by composing tryZip with a fromRight. What's more, the mentioned package contains an automatic Template Haskell deriver for Zippable instances, so you don't have to write the above instance definition yourself. The implementation is by Joachim Breitner. Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

Why is there no Zippable class? There is.
You can use Data.Zippable from http://hackage.haskell.org/package/bff.
It gives you a function
tryZip :: Zippable k => k a -> k b -> Either String (k (a,b))
The Either in the return type is to capture an error message in case the two structures are not of the same shape.
This functionality can also be obtained from the generic programming library EMGM, with the function zip :: FRep3 ZipWith f => f a -> f b -> Maybe (f (a, b)) You can use Template Haskell to generate the necessary FRep3 instances. Once you have those you get many other generic functions for free. See http://hackage.haskell.org/package/emgm -- Johan Jeuring
For example, for
data Tree a = Leaf a | Node (Tree a) (Tree a)
you would have:
instance Zippable Tree where tryZip (Leaf a) (Leaf b) = Right (Leaf (a,b)) tryZip (Node a1 a2) (Node b1 b2) = do z1 <- tryZip a1 b1 z2 <- tryZip a2 b2 return (Node z1 z2) tryZip _ _ = Left "Structure mismatch."
Of course, you can get an "unsafe" zip by composing tryZip with a fromRight.
What's more, the mentioned package contains an automatic Template Haskell deriver for Zippable instances, so you don't have to write the above instance definition yourself.
The implementation is by Joachim Breitner.
Ciao, Janis.
-- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Job Vranish 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.
Notice that you can always do this if the LHS is traversable and the RHS is Foldable (as a special case the RHS is the same as the LHS, since all foldables are traversable) : http://www.haskell.org/haskellwiki/Foldable_and_Traversable#Generalising_zip...

There is a Zip class in category-extras 's Control.Functor.Zip on hackage
that covers this use-case.
http://hackage.haskell.org/packages/archive/category-extras/latest/doc/html/...
It can basically be viewed as the ap of an Applicative functor chosen to be
the left inverse of a genericly definable 'unzip'. Though, a Zippable
functor isn't necessarily Applicative, because there is no reason it needs
to support pure -- a lot of zippable functors are comonads after all.
I wrote a short blog post on this:
http://comonad.com/reader/2008/zipping-and-unzipping-functors/
and one on the less powerful dual operations (less powerful because while
every Haskell Functor is strong, much fewer are costrong):
http://comonad.com/reader/2008/cozipping/
-Edward Kmett
On Thu, Jul 16, 2009 at 5:56 PM, Job Vranish
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2009/7/18 Edward Kmett
I wrote a short blog post on this: http://comonad.com/reader/2008/zipping-and-unzipping-functors/ and one on the less powerful dual operations (less powerful because while every Haskell Functor is strong, much fewer are costrong): http://comonad.com/reader/2008/cozipping/ -Edward Kmett
This is getting a bit OT, but I just wanted to comment that attempting to remove polymorphism from the Functor class (see thread a couple of days ago) means that not every Functor is strong. So strength for Functor would seem to require a fully polymorphic type. I don't know if costrength is 'easier' to derive for those 'restricted' Functors... - George

On Fri, Jul 17, 2009 at 10:37 PM,
2009/7/18 Edward Kmett
: I wrote a short blog post on this: http://comonad.com/reader/2008/zipping-and-unzipping-functors/ and one on the less powerful dual operations (less powerful because while every Haskell Functor is strong, much fewer are costrong): http://comonad.com/reader/2008/cozipping/ -Edward Kmett
This is getting a bit OT, but I just wanted to comment that attempting to remove polymorphism from the Functor class (see thread a couple of days ago) means that not every Functor is strong. So strength for Functor would seem to require a fully polymorphic type. I don't know if costrength is 'easier' to derive for those 'restricted' Functors..
Continuing the OT aside... Well, the monomorphic not-quite-Functor from that post is a pretty ugly concept categorically, and obviously doesn't qualify as a Hask endofunctor, given its limited scope. That isn't to say that occasionally you don't want a function that can map a ByteString to a ByteString a byte at a time -- merely that it is a different animal. ;) Strength does require polymorphism... which comes for free if we're talking about an actual endofunctor. The ad-hoc not-quite-Functor provides no guarantee that a member of that you have an instance of the class supporting pairs "instance Functor' F (X,Y)" or that if you do that you have an instance for the class supports pairs that you have one for the left side of the pair "instance Functor' F X" let alone that these definitions are consistent. But even if you grant all of that, regarding costrength, it makes things no easier. Costrength is effectively about the ability to check inside of a functor and see if in some Functor f, a value f x where x = Either a b has any b's and if so, it gives you one, otherwise it gives you an "f a", because no b's occurred. Clearly for some simple functors you can complete this operation. But, there are many for which you cannot. The most obvious problem case is f = (->) a, because you need an oracle that knows the outcome of an arbitrary Haskell function; Kurt Godel would roll over in his grave. Similarly you run into problems deciding the outcome of costrength on a stream of Eithers even if you limit your instances to the bare minimum of () and Either () (), because you'd need to decide equality of streams, which leads to a need for a halting problem oracle. See http://comonad.com/reader/2008/deriving-strength-from-laziness/ for more details. -Edward Kmett
participants (10)
-
Dan Weston
-
Edward Kmett
-
Jake McArthur
-
Janis Voigtlaender
-
Jeff Heard
-
Job Vranish
-
Johan Jeuring
-
Jules Bean
-
porges@porg.es
-
Ryan Ingram