Re: Contexts on data type declarations

1999-05-17 Thread Philip Wadler

Simon PJ writes:

> **  I therefore PROPOSE that when pattern matching on a constructor,
> **  any context on the data type declaration is ignored.
> Yell if you dislike this; otherwise I'll just add it to the 'bugs' page.

Bleah!  (Is that a loud enough yell?)

I'm happy with either of the following choices:

* Class constraints on constructors have effect everywhere (as in Hugs).
* Class constraints on constructors are eliminated (call it a typo if you must).

What you propose, I think, offers the worst of both worlds: all the
confusions of constraints on data declarations and none of the
advantages.

It may help if I explain my motivation in introducing class constraints
in data declarations.  Often, a type will make no sense without the
constraints; e.g., an association list type Alist a b makes no sense
unless Eq a holds.  The class constraints on data declarations were a
simple way for the user to ask the compiler to enforce this invariant.
They have compile-time effect only, no effect whatsoever on run-time
(in particular, no dictionaries should be passed).

You and some others have found this hard to accept, from which I conclude
that a compile-time language feature can be hard to understand if it is
not directly tied to run-time behaviour.  Live and learn.

> (Mark says it was very tricky to implement what Hugs does)

I can't imagine why.  Perhaps Mark can explain?  Cheers,  -- P






Re: Contexts on data type declarations

1999-05-17 Thread Philip Wadler

> So doesn't my proposal give you precisely what you want, and no more?

Because my interest is as much in documentation as in constraints on
how the program executes (I admit your method achieves the latter).
If I write, say,

  data Eq a => Assoc a b

then I'd like the signatures to ensure that the first argument of Assoc
is a member of class Eq wherever it appears.  Your technique guarantees
this is Assoc is used in a constructor, but not if used in a destructor.

>   But when you take a constructor *apart*, the invariant must hold
>   by construction: you couldn't have built the thing you are taking
>   apart unless invariant held.  So enforcing the invariant again is
>   redundant; and in addition it pollutes the type of selectors.

Your `redundant pollution' is exactly the effect I want to achieve!
Clearly, tastes differ.  Hope this clarifies,  -- P






RE: Contexts on data type declarations

1999-05-17 Thread Mark P Jones

Hi Phil!

| > (Mark says it was very tricky to implement what Hugs does)
| 
| I can't imagine why.  Perhaps Mark can explain?

I should clarify.  Arranging for constraints that appear in the types of
constructors to show up whenever that constructor is used --- whether in
an application or a pattern match --- was not at all tricky.  Indeed, it
seems very natural, and Hugs uses exactly the same code to deal with the
two cases.

The thing that did cause me grief was the section of code to calculate
the types of selectors.  There's no fundamental reason why it should
have been so difficult though.  After all, the rule for calculating the
context of a selector is pretty straightforward, at least in theory: you
just take the union of the contexts for all the constructors to which
that selector might be applied, and use that as the selector's context.
And if you look at the final version of the code, you'll not find any
hint of the battles I fought with it.  But it did cause me problems at
the time.  I don't honestly remember the details, but I think it had
more than a little to do with the task of matching up the constraints
from different constructors so that I could form the union, further
complicated by the interaction with rank 2 polymorphism (which is not
a Haskell 98 feature anyway).

I remember Lennart suggesting at the time that I was crazy to do it
this way anyway; he had just used the rules in the report to generate
code for selectors, and then used the normal type inference mechanisms
to figure out what the type should be.  I thought I could get better
error messages doing it my way, but perhaps I should have just taken
Lennarts advice!

All the best,
Mark







RE: Contexts on data type declarations

1999-05-18 Thread Simon Peyton-Jones

Folks,

Interesting!  Phil, Mark, and Jeff all have a different interpretation of
how contexts on how data type declarations work than I did.  So unless 
some other people chime in, I will therefore adopt their interpretation,
since (a) I'm in the minority and (b) it's not a big deal at all.

But just to make it clear what's under review here, consider

data Ord a => Tree a = MkTree {
  item :: a,
  kids :: [Tree a]
 }

We know that 
MkTree :: Ord a => a -> [Tree a] -> Tree a

But what type does the selector 'item' have?  Phil, Mark and Jeff think:

item :: Ord a => Tree a -> a

The same would apply to any use of MkTree in a pattern.  For example:

f (MkTree _ _) = True

would get the type

f :: Ord a => Tree a -> Bool

Speak now or put up with overloaded selectors!

Simon





RE: Contexts on data type declarations

1999-05-17 Thread Simon Peyton-Jones

> I'm happy with either of the following choices:
> 
> * Class constraints on constructors have effect everywhere 
> (as in Hugs).
> * Class constraints on constructors are eliminated (call it a 
> typo if you must).

I'd be delighted to eliminate them, but we had a long H98 debate 
about it (under John's chairmanship) and decided to keep them.

It depends what you mean by "have an effect everywhere".  That's what
I thought GHC implemented!   The effect you wanted is:
 
> It may help if I explain my motivation in introducing class 
> constraints
> in data declarations.  Often, a type will make no sense without the
> constraints; e.g., an association list type Alist a b makes no sense
> unless Eq a holds.  The class constraints on data declarations were a
> simple way for the user to ask the compiler to enforce this invariant.

When you *construct* a value, the overloaded constructor's
type does indeed ensure that you can't build it if the invariant
does not hold.

But when you take a constructor *apart*, the invariant must hold
by construction: you couldn't have built the thing you are taking
apart unless invariant held.  So enforcing the invariant again is
redundant; and in addition it pollutes the type of selectors.

So doesn't my proposal give you precisely what you want, and no more?

Simon






Re: Contexts on data type declarations

1999-05-18 Thread Erik Meijer

> Interesting!  Phil, Mark, and Jeff all have a different interpretation of
> how contexts on how data type declarations work than I did.  So unless 
> some other people chime in, I will therefore adopt their interpretation,
> since (a) I'm in the minority and (b) it's not a big deal at all.

I agree with Phil, Mark, and Jeff. Here is another explanation. The "meaning" of an 
overloaded function f :: P a => F a -> G a is the set of functions { f :: F a -> T a | 
P a}, now if we take the inverse of these functions we get the set { g :: T a -> F a | 
P a } which is the meaning of the qualified type g :: P a => T a -> F a. Selectors 
form "the inverse" of constructors (you know what I mean :-) hence they should be 
overloaded as well.

Erik






Re: Contexts on data type declarations

1999-05-18 Thread Olaf Chitil

Christian Maeder wrote:
> 
> > But what type does the selector 'item' have?  Phil, Mark and Jeff think:
> >
> >   item :: Ord a => Tree a -> a
> 
> This looks correct to me, too.
> 
> If an order is needed to construct a tree, say a search tree, the very same
> order is (or may be) needed to select an item, e.g. by searching!

But on the other hand a simple test 'emptyTree' will also have type
'Ord a => Tree a -> Bool' instead of just 'Tree a -> Bool' !
(compare with `null : [a] -> Bool')

However, I don't care what Haskell 98 does, because I don't use contexts on data
type declarations. I think, when writing the interface of an (abstract) data
type it is an important design decision which operations have which context. 


-- 
OLAF CHITIL, Lehrstuhl fuer Informatik II, RWTH Aachen, 52056 Aachen, Germany
 Tel: (+49/0)241/80-21212; Fax: (+49/0)241/-217
 URL: http://www-i2.informatik.rwth-aachen.de/~chitil/





RE: Contexts on data type declarations

1999-05-18 Thread Koen Claessen

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 ->

Re: Contexts on data type declarations

1999-05-25 Thread Christian Maeder


> > > But what type does the selector 'item' have?  Phil, Mark and Jeff think:
> > >
> > >   item :: Ord a => Tree a -> a
> > 
> > This looks correct to me, too.
> > 
> > If an order is needed to construct a tree, say a search tree, the very same
> > order is (or may be) needed to select an item, e.g. by searching!
> 
> But on the other hand a simple test 'emptyTree' will also have type
> 'Ord a => Tree a -> Bool' instead of just 'Tree a -> Bool' !
> (compare with `null : [a] -> Bool')

Indeed, I would expect the context, Ord a, for every function over Tree a.
(This is not so in the haskell98 report 4.2.1 for the empty set, NilSet,
and the class Eq.)

What is the use of an empty tree or set without context?

An abstract data type should not reveal its realization. An empty tree may
have been created by consecutive insertions and deletions. Nodes may only
be marked "deleted" and a test, emptyTree, may be less simple and may even
require the order from the context to traverse the tree. 

The context should be associated with the type constructor and not with the
(value) constructor.

> However, I don't care what Haskell 98 does, because I don't use contexts on data
> type declarations. I think, when writing the interface of an (abstract) data
> type it is an important design decision which operations have which context. 

Right, and if you change the implementation, the interface may also change
only due to changed contexts. (A set may be implemented by an unordered
list, such that adding is a simple list-cons, but deleting scans the whole
list and deletes all occurences. Should the context then move from the
constructor to the selector?)

Christian






Re: Contexts on data type declarations

1999-05-25 Thread Koen Claessen

Christian Maeder wrote:

 | An abstract data type should not reveal its realization.

Indeed! And therefore, an abstract datatype should not impose silly
restrictions on the context where they are not needed. How I implement a
set (for example using ordered binary trees or a hash table), is part of
the concrete representation of the datatype.

Koen.

--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.






Re: Contexts on data type declarations

1999-05-26 Thread Fergus Henderson

On 25-May-1999, Koen Claessen <[EMAIL PROTECTED]> wrote:
> Christian Maeder wrote:
> 
>  | An abstract data type should not reveal its realization.
> 
> Indeed! And therefore, an abstract datatype should not impose silly
> restrictions on the context where they are not needed. How I implement a
> set (for example using ordered binary trees or a hash table), is part of
> the concrete representation of the datatype.

Certainly we should never impose _silly_ restrictions where they are not
needed.  But not all restrictions are silly.  Some restrictions constitute
an important part of the interface.  Saying that a particular abstract
data type requires an ordering relation on its elements may well be an
important part of the interface.  And doing so does not reveal the
implementation.  The implementation could be a list, a red-black tree,
a 23-tree, a 234-tree, an AVL tree, or some other kind of data structure.
Stating the requirement for an ordering is just specifying the interface
requirements for that type, not disclosing the implementation.

Of course, the presence or absense of particular interface requirements
will certainly constrain the kinds of implementations that are possible,
but that should come as no surprise.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: RE: Contexts on data type declarations

1999-05-18 Thread Christian Maeder


> But what type does the selector 'item' have?  Phil, Mark and Jeff think:
> 
>   item :: Ord a => Tree a -> a

This looks correct to me, too. 

If an order is needed to construct a tree, say a search tree, the very same
order is (or may be) needed to select an item, e.g. by searching! 

Christian