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



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to