Scott Turner wrote:
>
> Alex Ferguson:
> >Kevin Atkinson:
> >> I take it that you are happy with names such as: [long list]
> >
> >Yes. Certainly I'm more than happy that types with completely different
> >signatures have different names.
>
> I also prefer to keep the names distinct when the meanings are distinct. I
> got to thinking about zip and unzip, zip2 and unzip2, etc. which gave a
> feeling of not being so distinct. Turns out, it's currying which prevents
> their signatures from being combined. Non-curried versions can be defined
> on general tuples, with just one pair of names:
>
> class Zippable tOfLists tsInList
> where
> zip' :: tOfLists -> [tsInList]
> unzip' :: [tsInList] -> tOfLists
> instance Zippable () ()
> where
> zip' () = repeat ()
> unzip' _ = ()
> instance Zippable ([t],[u],[v]) (t,u,v)
> where
> zip' (x:xs, y:ys, z:zs) = (x,y,z): (zap (xs, ys, zs))
> zip' _ = []
> unzip' ((x,y,z):more) = (x:xs, y:ys, z:zs)
> where
> (xs, ys, zs) = unzip' more
> instance Zippable ([t]) (t)
> instance Zippable ([t],[u]) (t,u)
> instance Zippable ([t],[u],[v],[w]) (t,u,v,w)
> etc. left as an exercise.
>
> Thus, the uglier cases on Kevin Atkinson's list can be addressed within
> Haskell's current overloading system.
>
I like that, but I wish we had a way to get the "head" and "tail" of
tuples, just as we do with lists, and combine them. Maybe a (:,)
operator that works like this:
a :, (b :, ()) = (a,b)
a :, () = UniTuple a
a :, (b,c) = (a,b,c)
a :, (UniTuple b) = (a,b)
Also allow pattern matching on this operator.
Then we could define the following:
instance Zippable () () -- as defined by Scott above
instance (Zippable b' b) => Zippable ([a] :, b') (a :, b) where
zip' (h :, t) =
case (h :, (zip' t)) of
([] :, _) -> []
(_ :, []) -> []
(x:xs :, y:ys) -> (x :, y) : zip' (xs :, ys)
unzip' ((x :, y): more) = (x:xs :, unzip' (y:ys)) where
(xs :, ys) = unzip' more
unzip' [] = ([] :, unzip' []) -- [] takes on three different types
here!
Thus we get Zippable instances for all tuples for free.
This also allows us to define Show, Read, Eq, and Ord instances for all
tuples in one fell swoop just as it allows for Zippable.
This seems a little too obvious to me. Has it been suggested and shot
down before?
Matt Harden