Simon Peyton-Jones wrote:
| Speak now or put up with overloaded selectors!
I don't know if this is of any interest to this discussion, but
the way I like interpreting a definition like:
data Eq a => Set a = MkSet [a]
is that every set knows how to compare its elements. Unfortunately,
this is not how it currently works in Haskell, but it is how it should
work.
Here is how I currently implement such sets:
data Set a = MkSet [a] (EqOper a)
type EqOper a = a -> a -> Bool
What this means is that I have to know how to compare elements for
equality when I *construct* a set:
empty :: Eq a => Set a
empty = MkSet [] (==)
Or maybe even:
mkSet :: Eq a => [a] -> Set a
mkSet xs = MkSet xs (==)
But not when I *use* a set:
diff :: Set a -> Set a -> Set a
diff (MkSet xs (==)) (MkSet ys _) =
MkSet (filter (\x -> not (any (x==) ys)) xs)
It makes the interface to `Set' and its operators more abstract,
because the `Set's know themselves what operations are needed,
the user of `diff' does not have to be bothered by that.
The only time the programmer needs to know about this is when
(s)he has to choose the representation of sets, that is, at
construction time.
It is also very convenient, for example to make types like these
instances of one-parameter type classes, a problem that is described
and solved in a different way in Simon's Bulk class paper.
It doesn't always work of course, because sometimes the functions
to *construct* an element in such a type is also a method in the class,
but surprisingly often it is not!
I am currently using this technique to make a Haskell'98 version
of TkGofer, and to implement a version of Lava without multiple
parameter type classes.
It would be great if Haskell-2 would support these ideas
in some way or another. This means that destructing
(pattern-matching or selecting) should *not* have the
context restriction inherited from the datatype declaration.
Regards,
Koen.
PS. I include a message I sent to comp.lang.functional a while
ago where I apply a similar trick to help somebody who
posed a question.
--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.
---------------------------------------------------------------------
>From [EMAIL PROTECTED] Tue May 18 15:43:07 1999
Date: Tue, 27 Apr 1999 10:18:13 +0200
From: Koen Claessen <[EMAIL PROTECTED]>
To: Matti Nykanen <[EMAIL PROTECTED]>
Bcc: John Hughes <[EMAIL PROTECTED]>
Newsgroups: comp.lang.functional
Subject: Re: Haskell Q: constructors vs. constructor classes?
In comp.lang.functional, Matti Nykanen wrote:
| class Strategy memory where
| doneWork :: memory datum -> Bool
| moreWork :: [datum] -> memory datum -> memory datum
| lessWork :: memory datum -> (datum,memory datum)
:
| instance Strategy [] where
| -- trivial
:
| instance Ord a => Strategy (Heap a) where
| -- ???
There are a number of solutions to this.
The first and easiest one is to use multiple parameter type classes.
Unfortunately, this can only be done in extensions of Haskell at the
moment. You might try to start Hugs with the flag -98.
The idea is to restrict `datum' as well as `memory':
class Strategy memory datum where
doneWork :: memory datum -> Bool
moreWork :: [datum] -> memory datum -> memory datum
lessWork :: memory datum -> (datum,memory datum)
Now you can make lists an instance. List can handle any `a':
instance Strategy [] a where
-- as before
You can also make `Heap' an instance. Heaps however, can only handle `a'
that have an ordering on them.
instance Ord a => Strategy Heap a where
-- definitions
This is one solution. The drawback is that it does not work with
Haskell'98. But there is hope!
------------------------------------------------------------------
In some cases, you can do a neat trick. Suppose you have a primitive Heap
implementation:
data PrimHeap a -- ordered tree
= Empty
| Node a (PrimHeap a) (PrimHeap a)
Now make a new datatype `Heap a', that contains this PrimHeap, but also
knows how to compare the elements!
type Order a
= a -> a -> Ordering
data Heap a
= MkHeap (Order a) (PrimHeap a)
A heap now also knows how to order its elements, but only internally!
Now introduce a function that construct an empty heap:
empty :: Ord a => Heap a
empty = MkHeap compare Empty
This function is the only function on Heaps that needs `Ord a' in the
context. Because from now on, every heap knows how to order its elements,
so you do not need `Ord a' in your context in any other operation. For
example, the function which inserts elements in a heap:
insert :: a -> Heap a -> Heap a -- no `Ord a' in context;
insert a (MkHeap comp heap) = -- because `comp' knows how to compare!
MkHeap comp (ins a heap)
where
ins a Empty =
Node a Empty Empty
ins a (Node b left right) =
case a `comp` b of
LT -> Node b (ins a left) right
EQ -> Node b left right
GT -> Node b left (ins a right)
This works similarly for other operations such as `search',
`merge', etc.
Since none of the operations working on heaps require an ordering on a in
the context anymore, you can safely make Heap an instance of Strategy:
instance Strategy Heap where
doneWork = isEmpty
moreWork new old = foldr insert old new
lessWork heap = (hhead heap, htail heap)
A bit more involved, but it works in Haskell'98.
----------------------------------------------------------------
Postscriptum: the proposed solution works only if the functions that
_create_ the objects (such as `empty') are not member functions of the
class, because these functions need the contexts. Also, the operations
that work _with_ the objects always need access to the objects.
The following method would not be possible to do:
mergeAll :: [datum] -> [memory datum] -> memory datum
Because what would you do in the case the list with the heaps in it
is empty?
John Hughes has proposed an extension to Haskell in which the condition
that a `Heap a' knows how to order its elements, or that `Set a' knows
equality on its elements, or that `Hash a' knows how to hash its elements,
is generally expressed as `Heap a', `Set a' and `Hash a' are all
well-formed types.
This extension would incorporate a general solution to this problem.
------------------------------------------------------------------
Regards,
Koen.
--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.