--------------15FB7483794BDF32446B9B3D
Content-Type: text/plain; charset="us-ascii"
Christoph Herrmann wrote:
> I always find it annoying to have a lot of
> auxiliary functions for selecting elements of
> tuples. It would be nice to have, e.g.,
> an infix operator, say "#", that takes a tuple
> and an integer >constant< and delivers one element
> out of the tuple
You can (almost) do this with Haskell 1.3 constructor classes. I enclose
a module that gives you overloaded selector functions called part1,
part2, part3, and so on, that work on all tuples sizes (upto an
arbitrary limit, in the enclosed code chosen to be 4 :-).
However, because the way constructor classes work in Haskell 1.3, it only
almost works. For instance, I had to number the parts from right to left
to get it to work. So, this turns out to be a good example where the rather
annoying restrictions (or lack of expressiveness) that constructor classes
have, pop up. Two problem are:
1. If "T a b" is a type, then the type constructor "\ b -> T a b" can be
expressed as "T a", but the type constructor "\ a -> T a b" CAN NOT be
expressed. This severely restricts the ways in which the same type can
be declared an instance of different constructor classes and is the reason
why I had to number the parts from right to left to get the selector
functions to work.
2. Classes can only be related in the subclass hierarchy if they work on
type constructors of the same kind. For example, the Monad class is for
types of kind *->*. State monads would have an extra parameter in the
type, so a class StateMonad would be for types of kind *->*->*. This
means that StateMonad can not be a subclass of Monad, which otherwise
seems very natural. Also, without this relationship, types of the form
"(Monad (m s),StateMonad m) => ...", which are currently illegal in
Haskell, would easily arise, I presume. The same problem occurs in my
selector function solution in the type of functions like
swaparound t = (part1 t,part2 t, part3 t)
If problems like these are solved, then the problem of selector
functions is solved too, or at least reduced to a minor practical issue.
(And while I am at it...) It would of course also be nice to have proper
record types with subtyping. This would provide the most general and
convenient solution to the selector function problem, I suppose. Isn't
it about time record types with subtyping were integrated into widely
used functional languages? The type inference problem has been solved
many times over by now (see, e.g., Didier Remy's Projective ML), hasn't
it? A problem then is how subtyping should be integrated with the
Haskell class system. Wouldn't it be really great if someone solved
that!
Thomas H
--------------15FB7483794BDF32446B9B3D
Content-Disposition: inline; filename="TupleSelectors.hs"
Content-Type: text/plain; charset="us-ascii"; name="TupleSelectors.hs"
module TupleSelectors where
-- Classes for tuple component selectors.
-- Note: parts are numbered from right to left.
-- Size 2 tuples --
class Tuple2 p where
part2 :: p a b -> a
part1 :: p a b -> b
instance Tuple2 (,) where
part2 (a,b) = a
part1 (a,b) = b
-- Size 3 tuples --
class Tuple3 t where
part3 :: t a b c -> a
instance Tuple3 (,,) where
part3 (a,b,c) = a
instance Tuple2 ((,,) a) where
part1 (a,b,c) = c
part2 (a,b,c) = b
-- Size 4 tuples --
class Tuple4 q where
part4 :: q a b c d -> a
instance Tuple4 (,,,) where
part4 (a,b,c,d) = a
instance Tuple3 ((,,,) a) where
part3 (a,b,c,d) = b
instance Tuple2 ((,,,) a b) where
part2 (a,b,c,d) = c
part1 (a,b,c,d) = d
-- and so on for other sizes...
--------------15FB7483794BDF32446B9B3D
Content-Disposition: inline; filename="TestSelectors.hs"
Content-Type: text/plain; charset="us-ascii"; name="TestSelectors.hs"
module TestSelectors where
import TupleSelectors
p = ("Hej",False)
p1p = part1 p
p2p = part2 p
-- p3p = part3 p -- type error
t = ("Hej",False,not)
p1t = part1 t
p2t = part2 t
p3t = part3 t
q = ("Hej",False,not,())
p1q = part1 q
p2q = part2 q
p3q = part3 q
p4q = part4 q
swaparound t = (part1 t,part2 t, part3 t)
-- type inference problems (context reduction problems)
--------------15FB7483794BDF32446B9B3D--