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

Job Vranish jvranish at gmail.com
Thu Jul 16 23:58:42 EDT 2009


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 <ryani.spam at gmail.com> 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<westondan at imageworks.com>
> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090716/75eac8ea/attachment.html


More information about the Haskell-Cafe mailing list