Question about typing

Matt Harden matth@mindspring.com
Sat, 07 Apr 2001 20:46:00 -0500


In a lazy language like Haskell, a list is essentially the same as a
lazy stream, though I'm not well versed in the parallel stuff...

Anyway, it can be quite desirable to be able to "zip" together data
structures other than lists; trees or arrays for example.  The standard
prelude and library does not include any class to do this.  I played
with this awhile back, and came up with the following:

   module Zip where
   import Prelude hiding (zip, zipWith, zipWith3, zip3)

   class (Functor f) => ZipFunctor f where
      -- "zap" stands for "zip apply"
      -- it applies a set of functions to a set
      -- of arguments, producing a set of results
      zap :: f (a->b) -> f a -> f b

   instance ZipFunctor [] where
      (f:fs) `zap` (x:xs) = f x : fs `zap` xs
      _ `zap` _ = []

   instance ZipFunctor Maybe where
      (Just f) `zap` (Just x) = Just (f x)
      _ `zap` _ = Nothing

   zipWith  :: (ZipFunctor f) => (a->b->c) -> f a -> f b -> f c
   zipWith  f xs ys = f `fmap` xs `zap` ys

   zipWith3 :: (ZipFunctor f) => (a->b->c->d)->f a->f b->f c->f d
   zipWith3 f xs ys zs = f `fmap` xs `zap` ys `zap` zs

   zip  :: ZipFunctor f => f a -> f b -> f (a,b)
   zip  = zipWith  (,)
   zip3 :: ZipFunctor f => f a -> f b -> f c -> f (a,b,c)
   zip3 = zipWith3 (,,)

One can easily create ZipFunctor instances for trees and other data
structures.  I can provide examples if you like.  With multiple
parameter type classes (MPTCs, they are not in Haskell 98) as well as
functional dependencies (also not in h98), one can also create a
"Zippable" class to generalize the zip function over multiple tuple
types and eliminate zip3, zip4, etc.

I don't know of any way to make option 1 below equivalent to the other
two; I think it is impossible with Haskell's current type systems. 
However, you can create an "Id" type, which is a wrapper that holds
exactly one instance of another type.  Id happens to trivially be a
Functor and a Monad, is also trivially a ZipFunctor, and can be defined
as a newtype to eliminate overhead in the compiled program.  Then you
would have option 1 as follows:
   1. Adding two integers together: Id Int -> Id Int -> Id Int
The function for all three options would then be (zipWith (+)).

Hope this helps,
Matt


andrew@andrewcooke.free-online.co.uk wrote:
> 
> Is there a class that both lists and lazy streams could implement, so
> that zip et al could be more general?  The distinction between 2 and 3
> below seems a bit arbitrary.  Something like fmap/Functor?  (If there
> is, I guess it could apply to 1 too?; if not, why not - is it
> impractical (efficiency?) or just wrong?)
> 
> Curious,
> Andrew
> 
> On Thu, Apr 05, 2001 at 06:19:30PM +0100, Toby Watson wrote:
> > Intuitively the following scenarios seem to be related, can anyone point my
> > in the direction of formal work on this, or give me the formal terms I need
> > to search around?
> >
> > 1. Adding two integers together: Int -> Int -> Int
> >
> > 2. Adding two lists of Integers together: [Int] -> [Int] -> [Int]
> >
> > 3. Adding two lazy streams of integers together, possibly in seperate
> > (parallel) processes for example.
> >
> >
> > cheers,
> > Toby
> >
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> 
> --
> http://www.andrewcooke.free-online.co.uk/index.html
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe