
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

Toby Watson writes: | 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] If you're adding each element of the first list to the element in the corresponding position in the second list, it's usually called zipping. The zipWith function in the prelude takes as its parameter a function of type a->b->c (your scenario 1) and returns a function of type [a]->[b]->[c] (your scenario 2). If you're adding every element of the first list to every element of the second list, it's sometimes called diagonalisation. | 3. Adding two lazy streams of integers together, possibly in seperate | (parallel) processes for example. I think the term `zipping' can apply to most container types, even those with branching structures which don't look like half an actual zip. Regards, Tom

On Fri, 6 Apr 2001, Tom Pledger wrote:
If you're adding every element of the first list to every element of the second list, it's sometimes called diagonalisation.
I do not know where this definition came from but it does not make sense to me. It is zipping that looks like a diagonalization, not the other way around. [f ai bj | ai <- a, bj <- b] This looks like an outer product of two vectors, or a matrix represented as a linear vector of dimension n x m, where n = length a, m = length b. If f = (*) then it is really the outer product. [ai * bj | (ai, bj) <- zip a b] But this is a list of diagonal elements of the outer product above, providing that n == m. Jan

Tom Pledger wrote:
Toby Watson writes: | 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]
If you're adding each element of the first list to the element in the corresponding position in the second list, it's usually called zipping. The zipWith function in the prelude takes as its parameter a function of type a->b->c (your scenario 1) and returns a function of type [a]->[b]->[c] (your scenario 2).
Jeff Lewis implemented zip comprehensions in the latest versions of both GHC and Hugs. This notation provides special syntax to deal with the second case above nicely. You can say: [x + y | x <- [1,2,3,4,5] | y <- [5,6,7,8]] to get: [6,8,10,12] The shorther list determines the final length (could of course be infinite.) It's an extension of the usual syntax, so multiple generators are OK too: [x + y | x <- [1,2,3,4,5], z <- [3, 4, 5], (x+z) `mod`2 == 1 | y <- [5,6,7,8], y `mod` 2 == 0] gives: [7, 10] It's a great notation that avoids zipWith's. (You need to start hugs with -98 and GHC needs -fglasgow-exts for zip comprehensions to be recognized.) -Levent.

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

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

On Sat, Apr 07, 2001 at 08:46:00PM -0500, Matt Harden wrote:
In a lazy language like Haskell, a list is essentially the same as a lazy stream
Sorry. I've been using Haskell a few months now, and I really did know that, but got so confused going round in circles with a similar problem I'm working on myself that nothing was clear any more. Thanks for the clear reply + class. Andrew -- http://www.andrewcooke.free-online.co.uk/index.html

Sat, 07 Apr 2001 20:46:00 -0500, Matt Harden
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
This is nice as long as the type is fully polymorphic. Unfortunately this is not always the case in reality. Let's take unboxed flat sequences (unboxed vectors). Imagine we have data UVector a class Seq c a | c -> a instance Seq (UVector Bool) Bool instance Seq (UVector Char) Char instance Seq (UVector Int) Int -- etc. (in fact I do have this). Class Seq provides various operations common to sequences. There are no problems with operations involving sequences of the same type (e.g. splitAt), but it's not obvious how to handle map and zipWith. BTW. Alternatively it could be expressed thus: data UVector a class Seq c a instance Seq UVector Bool instance Seq UVector Char instance Seq UVector Int -- etc. but it disallows certain abstractions, like conversion of an immutable container to a mutable container independently of its kind. This doesn't change the problem with map. I found a way to express map and zipWith, but it's quite ugly. I would be happy to have a better way. class Map c' a' c a | c' -> a', c -> a, c' a -> c, c a' -> c' where map :: (a' -> a) -> c' -> c class (Map c a c a, ...) => Seq c a -- Class Seq requires method map which doesn't chage the -- element type. instance Map [a] a [b] b -- map on lists is more general than mere Seq requires: -- it's fully polymorphic wrt. the element type. instance Seq [a] a -- This instance alone implies only Map [a] a [a] a. class IArray c a -- This is a class of immutable arrays, provided by ghc. newtype IArrayToVector c a = V (c Int a) -- Convert an immutable array to a flat sequence. -- (In fact I have done this a bit differently; it doesn't -- matter now.) instance (IArray c a', IArray c a) => Map (c Int a') a' (c Int a) a -- As long as both element types are ok for an immutable array, -- vector derived from the array can be mapped from one to -- the other. instance IArray c a => Seq (c Int a) a -- This implies only Map (c Int a) a (c Int a) a. data UArray k a instance IArray UArray Bool instance IArray UArray Char instance IArray UArray Int -- etc. This is provided by ghc. type UVector = IArrayToVector UArray -- There are instances Seq (UVector a) a for particular choices -- of a, and more: instances Map (UVector a') a' (UVector a) a -- for particular choices of a' and a. -- zipWith is similar to map, only more complicated: class ZipWith c1 a1 c2 a2 c a | c1 -> a1, c2 -> a2, c -> a, c1 a -> c, c a1 -> c1, c2 a -> c, c a2 -> c2 where zipWith :: (a1 -> a2 -> a) -> c1 -> c2 -> c -- zipWith3 is even more ugly. An alternative way is this: remove Map class, have map as a standalone function which converts a container to a list, maps the list, and converts it back. Disadvantages are that it applies only to things which can be sensibly converted to a list, and that if mapping of a dictionary is specified as preserving the keys (actually the key is in the function argument but not in the result), then it must recreate the dictionary structure from scratch. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

On Sun, Apr 08, 2001 at 11:34:45AM +0000, Marcin 'Qrczak' Kowalczyk wrote:
... I found a way to express map and zipWith, but it's quite ugly. I would be happy to have a better way.
class Map c' a' c a | c' -> a', c -> a, c' a -> c, c a' -> c' where map :: (a' -> a) -> c' -> c ... -- zipWith is similar to map, only more complicated: class ZipWith c1 a1 c2 a2 c a | c1 -> a1, c2 -> a2, c -> a, c1 a -> c, c a1 -> c1, c2 a -> c, c a2 -> c2 where zipWith :: (a1 -> a2 -> a) -> c1 -> c2 -> c ...
You raise many interesting question, but let me ask about one: why the specific choice of functional dependencies above? Why is "c' a -> c" necessary for Map? Why doesn't ZipWith include, e.g., "c1 a2 -> c2"? (I don't have a lot of experience with these functional dependencies...)

Sun, 8 Apr 2001 12:38:27 -0400, Dylan Thurston
class Map c' a' c a | c' -> a', c -> a, c' a -> c, c a' -> c' where map :: (a' -> a) -> c' -> c ... -- zipWith is similar to map, only more complicated: class ZipWith c1 a1 c2 a2 c a | c1 -> a1, c2 -> a2, c -> a, c1 a -> c, c a1 -> c1, c2 a -> c, c a2 -> c2 where zipWith :: (a1 -> a2 -> a) -> c1 -> c2 -> c ...
You raise many interesting question, but let me ask about one: why the specific choice of functional dependencies above? Why is "c' a -> c" necessary for Map?
To make the type of "map f xs" determinable from types of f and xs. The idea is that instances of map will be made only for "the same" container applied to potentially different element types (where the concept of "the same" is not formal, because c is the container already applied to the element type). If map could arbitrarily convert the shape of containers, there would be more ambiguities. In particular "map f (map g xs)" would be always ambiguous (nothing says what container to use for the intermediate value). Conversion is done similarly to fromIntegral: as composition of functions which convert a container to and from a common universal type: a list (which is a list of pairs in the case of dictionaries). A perhaps unusual thing is that when the instance of a class like Map is determined to be [a] a [b] b, then type variables a and b become unconstrained. I'm not sure if it causes problems. Generally it seems to be important which exactly type variables are constrained, e.g. for resolving ambiguities and for the monomorphism restriction. The bright side of this is that even though map is generally overloaded over element types, it has an instance of the type equivalent to Prelude's map: fully polymorphic wrt. element types.
Why doesn't ZipWith include, e.g., "c1 a2 -> c2"?
When a is determined (it must be determined by other means anyway, otherwise the instance is ambiguous, and c1 a2 -> c2 would not help here), c1 a -> c, c a2 -> c2. So this dependency is implied by others. I hope I haven't overlooked anything. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK
participants (8)
-
andrew@andrewcooke.free-online.co.uk
-
Dylan Thurston
-
Jan Skibinski
-
Levent Erkok
-
Matt Harden
-
qrczak@knm.org.pl
-
Toby Watson
-
Tom Pledger