Re: [Haskell] PROPOSAL: class aliases

2005-10-27 Thread Ross Paterson
On Thu, Oct 13, 2005 at 05:51:36AM -0700, John Meacham wrote:
 On Thu, Oct 13, 2005 at 12:21:41PM +0100, Simon Peyton-Jones wrote:
  Anyway, my main point is: would a smaller change not suffice?
 
 I do not think it suffices.
 
 We could extend the supertyping relationship some more to make it
 suitable, but I think we will end up with the exact same proposal but
 with different terminology :)

For concreteness, here's a slight narrowing of Simon's version.
Given your H98 classes

class Additive a where
(+) :: a - a - a
zero:: a

class Additive a = Negative where
(-) :: a - a - a
negate  :: a - a

x - y   = x + negate y
negate x = zero - x

class Multiplicative a where
(*) :: a - a - a
one :: a

extend the class syntax with an annotation on the assumptions (! for now),
to allow

class (Show a, !Additive a, !Negative a, !Multiplicative a) =
Num a where
fromInteger :: Integer - a

one = fromInteger 1
zero= fromInteger 0

(This is for illustration -- I'm not claiming this is the ideal factoring
of the Num class.)

The ! annotations would be ignored during type inference.  Their only
meaning is

(a) the class declaration for Num may include defaults for the methods
of the !'d superclasses,

(b) an instance declaration for Num also defines instances for the !'d
superclasses, and thus may include definitions for the methods of Num
and those superclasses.  Any methods of these classes not defined
in the instance are assigned default definitions, with defaults in
the Num class overriding any in the superclasses.

Thus if a Num instance is given, a Show instance must also be in scope
(as now), but Additive, Negative and Multiplicative instances cannot be
given, e.g.:

instance Show Int65536 where
showsPrec n = showsPrec n . toInteger

instance Num Int65536 where
(+) = primPlusInt65536
(-) = primMinusInt65536
(*) = primMultInt65536
fromInteger = primFromInteger65536

In comparision with the class alias proposal, this loses aliasing, but
retains the ability to define defaults for superclasses, which is what
I've been missing for ages.

All these proposals need to address repeated inheritance, as in an
example from Davis Menendez:

class (!Functor m) = Monad m where { fmap = liftM; ... }
class (!Functor d) = Comonad d where { fmap = liftD; ... }

With the above rules, it would be illegal to define instances of both
these classes for the same type, but one could define

class (!Monad f, !Comonad f) = MonadComonad f where
...

as long as either the class includes a default definition of fmap,
or the instance includes a definition:

instance MonadComonad Id where
fmap f (Id x) = Id (f x)
...

MPTCs raise extra issues, like

class (!Functor f, !Functor g) = Something f g where
fmap = ...

Which Functor is being given a default fmap?  I'd prefer to avoid this
by requiring that the !'d assumptions have exactly the same arguments
as the class being defined.

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-15 Thread Udo Stenzel
Wolfgang Jeltsch wrote:
 This does mean that you want to treat classes without methods special, 
 doesn't 
 it?

Not quite, I'm actually not sure if I want this, I just noted that it
was possible. :)  As David Menendez pointed out, empty classes probably
aren't that useless.

Anyway, not treating empty classes specially and just making the
universal instance explicit may be enough.  Foo is declared an alias for
Bar by writing:

class Foo a = Bar a
instance Foo a = Bar a

The latter is not Haskell98, but a harmless extension.  Doing it this
way feels better than introducing new syntax and semantics, at least
to me.


Udo.
-- 
Don't you know that alcohol for a young man is nothing but slow poison?
Slow poison, eh? Well, I'm not in any hurry.
-- gefunden auf http://c2.com/cgi-bin/wiki?SlowPoison


signature.asc
Description: Digital signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-14 Thread Wolfgang Jeltsch
Am Donnerstag, 13. Oktober 2005 12:22 schrieb John Meacham:
 [...]

 although perhaps

class alias FooBar a = (Foo a, Bar a)  where ...

 since the new name introduced usually appears to the left of an equals
 sign.

Yes, exactly.

 This also solves the problems of where to put new supertype constraints.

class alias FooBar a = Show a = (Foo a, Bar a)  where ...

 should do nicely.

What is the difference between this and the following:

class alias FooBar a = (Show a, Foo a, Bar a) where ...

 [...]

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-14 Thread Wolfgang Jeltsch
Am Donnerstag, 13. Oktober 2005 15:58 schrieb Udo Stenzel:
 [...]

 Further, if classes with no methods have no use currently, this universal
 instance could be compiler generated whenever a class without methods is
 declared.

This does mean that you want to treat classes without methods special, doesn't 
it?  I think, that it is generally not a good thing to have special treatment 
for a specific case.

 [...]

 Udo.

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-14 Thread Wolfgang Jeltsch
Am Donnerstag, 13. Oktober 2005 15:43 schrieb Simon Peyton-Jones:
 John

 Replying just to you to avoid spamming everyone.

Hmm, you did write to the list as well...

 [...]

 I don't agree.  What do you mean by distinct types?  In H98 both of
 these are ok:

   f :: CD a = ty
   f = ...code...

   g :: (C a, D a) = ty
   g = f

This is not okay.  Hugs gives this error message (with ty = a):

Cannot justify constraints in explicitly typed binding
*** Expression: g
*** Type  : (C a, D a) = a
*** Given context : (C a, D a)
*** Constraints   : CD a

 [...]

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases (revised)

2005-10-14 Thread Remi Turk
On Thu, Oct 13, 2005 at 05:53:15PM -0700, John Meacham wrote:
 I have revised the proposal and put it on the web here:
 
  http://repetae.net/john/recent/out/classalias.html
 
 changes include a new, clearer syntax, some typo fixes, and a new
 section describing how class aliases interact with superclasses.
 
 I will update that web page with any new devolpments.
 
 John

Hi,

it sounds like a great idea. And as I don't really have anything
more fundamental to say about it, I'll invoke Wadlers Law now:

What about

 class Eq a = alias Num a = (Additive a, Multiplicative a)
or perhaps
 class alias Eq a = Num a = (Additive a, Multiplicative a)

instead of

 class alias Num a = Eq a = (Additive a, Multiplicative a)

If Eq a, then Num a is an alias for ...


Groeten,

Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Wolfgang Jeltsch
Am Donnerstag, 13. Oktober 2005 02:00 schrieb John Meacham:
 [...]

At a first look, this looks really nice.

 We allow new constructs of this form (the exact syntax is flexible of
 course): 

   class alias (Foo a, Bar a) = FooBar a where
 foo = ...

 what this does is declare 'FooBar a' as an alias for the two constraints
 'Foo a' and 'Bar a'. This affects two things.

Wouldn't it be better to write it this way:

class alias (Foo a, Bar a) = FooBar a where ...

(Foo a, Bar a) = FooBar a normally means that a type is an instance of Foo 
and Bar if it is an instance of FooBar but in the case of aliases, a type is 
also an instance of FooBar if it is an instance of Foo and Bar.

 [...]

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 12:08:27PM +0200, Wolfgang Jeltsch wrote:
  We allow new constructs of this form (the exact syntax is flexible of
  course): 
 
class alias (Foo a, Bar a) = FooBar a where
  foo = ...
 
  what this does is declare 'FooBar a' as an alias for the two constraints
  'Foo a' and 'Bar a'. This affects two things.
 
 Wouldn't it be better to write it this way:
 
   class alias (Foo a, Bar a) = FooBar a where ...
 
 (Foo a, Bar a) = FooBar a normally means that a type is an instance of Foo 
 and Bar if it is an instance of FooBar but in the case of aliases, a type is 
 also an instance of FooBar if it is an instance of Foo and Bar.

Yeah, I totally agree. it would also reduce confusion with superclasses
and emphasises the fact that the two sides are equivalent everywhere.
(except instance heads)

although perhaps

   class alias FooBar a = (Foo a, Bar a)  where ...

since the new name introduced usually appears to the left of an equals
sign. This also solves the problems of where to put new supertype
constraints.

   class alias FooBar a = Show a = (Foo a, Bar a)  where ...

should do nicely. 

if nothing better comes along I will update my copy of the proposal
with this new syntax...

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Malcolm Wallace
John Meacham [EMAIL PROTECTED] writes:

 = Class Aliases =
 
 This is a proposal for a language extension which will hopefully mitigate
 the issues holding back evolution of the standard prelude as well as provide
 useful class abstraction capabilities in general.

I like your proposal a lot.  Do you have an implementation of it in jhc?

   class Foo a where
 foo :: a - Bool
 foo x = False
 
   class Bar b where
 bar :: Int - b - [b]
 
   class alias (Foo a, Bar a) = FooBar a where
 foo = ...
 bar = ...

One thought: how will class aliases interact with type inference?
e.g. if a declaration contains only a call to 'foo', should we infer
the constraint Foo a, or FooBar a?  Can there ever be a situation where
choosing the more specific dictionary could leave us without a 'bar'
method at some later point in the computation?  (cf. up-casting and
down-casting in OO languages).

If I declare a function

baz :: Bar a = ...

and then pass it a value which actually has a FooBar dictionary rather
than just a Bar, will the implementation be able to find the right
offset in the dictionary for the 'bar' method?  How?  (I know jhc
eliminates dictionaries at compile-time, but other implementations
do not.)

Regards,
Malcolm
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Andres Loeh
 One thought: how will class aliases interact with type inference?
 e.g. if a declaration contains only a call to 'foo', should we infer
 the constraint Foo a, or FooBar a?  Can there ever be a situation where
 choosing the more specific dictionary could leave us without a 'bar'
 method at some later point in the computation?  (cf. up-casting and
 down-casting in OO languages).

 If I declare a function

 baz :: Bar a = ...

 and then pass it a value which actually has a FooBar dictionary rather
 than just a Bar, will the implementation be able to find the right
 offset in the dictionary for the 'bar' method?  How?  (I know jhc
 eliminates dictionaries at compile-time, but other implementations
 do not.)

The way I understand the proposal, there are no FooBar dictionaries
ever. John said that this can be translated by a source-to-source
translation, so internally, a FooBar dictionary *is* a Foo and a
Bar dictionary.

How much static checking can be done before desugaring the code? Will
it be possible to give sensible error messages, or will those mention
the internal classes that the alias is supposed to hide?

Cheers,
  Andres

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Malcolm Wallace
Andres Loeh [EMAIL PROTECTED] writes:

 The way I understand the proposal, there are no FooBar dictionaries
 ever. John said that this can be translated by a source-to-source
 translation, so internally, a FooBar dictionary *is* a Foo and a
 Bar dictionary.

Ah yes, I was misled by the syntax, which suggested a superclass
relationship, and therefore a combined dictionary.  I see now the
improved syntax proposal which makes the absence much clearer.

Regards,
Malcolm
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 12:46:21PM +0200, Andres Loeh wrote:
  One thought: how will class aliases interact with type inference?
  e.g. if a declaration contains only a call to 'foo', should we infer
  the constraint Foo a, or FooBar a?  Can there ever be a situation where
  choosing the more specific dictionary could leave us without a 'bar'
  method at some later point in the computation?  (cf. up-casting and
  down-casting in OO languages).
 
  If I declare a function
 
  baz :: Bar a = ...
 
  and then pass it a value which actually has a FooBar dictionary rather
  than just a Bar, will the implementation be able to find the right
  offset in the dictionary for the 'bar' method?  How?  (I know jhc
  eliminates dictionaries at compile-time, but other implementations
  do not.)
 
 The way I understand the proposal, there are no FooBar dictionaries
 ever. John said that this can be translated by a source-to-source
 translation, so internally, a FooBar dictionary *is* a Foo and a
 Bar dictionary.

This is correct. perhaps 'class synonym' might be a better name? 
FooBar a and (Foo a,Bar a) are actually equivalent as if it were
replaced via a textual macro substitution. the only place they are treated
differently is in instance heads as declaring an instance for an alias
will declare instances for all of its components. 

 
 How much static checking can be done before desugaring the code? Will
 it be possible to give sensible error messages, or will those mention
 the internal classes that the alias is supposed to hide?

A simple implementation would mention all the 'internal' classes. but
ghc already knows to replace [Char] with String, it could do something
similar looking for when a bunch of constraints can be simplified into
a shorter alias and printing that.

It also might be useful to have a pragma for the Haskell 98 names
saying error messages should always be in terms of them when possible in
haskell 98 mode so people learning from haskell 98 books arn't confused.

perhaps something looking at the current names in scope could also be
done, like if you only have the aliased names in scope, print errors in
terms of those rather than the internal ones. 

How much this will be an issue in practice we will have to see. we
might have to experiment some to find the best method for producing
error messages.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 11:48:17AM +0100, Malcolm Wallace wrote:
 Andres Loeh [EMAIL PROTECTED] writes:
 
  The way I understand the proposal, there are no FooBar dictionaries
  ever. John said that this can be translated by a source-to-source
  translation, so internally, a FooBar dictionary *is* a Foo and a
  Bar dictionary.
 
 Ah yes, I was misled by the syntax, which suggested a superclass
 relationship, and therefore a combined dictionary.  I see now the
 improved syntax proposal which makes the absence much clearer.

Yeah, that has confused several people already. I wish I used the new
syntax in my original post, it really makes more sense. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Simon Peyton-Jones
| This is a proposal for a language extension which will hopefully
mitigate the
| issues holding back evolution of the standard prelude as well as
provide
| useful class abstraction capabilities in general.

A short summary would be type synonyms for class constraints.   You'd
definitely want the syntax to look as much like a type synonym decl as
possible.

I've considered this before, but never done anything about it because
superclasses are so close.  Specifically, what is the difference between

(i) class (C a, D a) = CD a
and
(ii)class alias CD a = (C a, D a)

Note that (i) is Haskell 98.

* In both cases one can write
f :: (CD a) = ...
   instead of the more voluminous
f :: (C a, D a)

* However with (i), for each type T one must write
instance C T where { ...meths for C... }
instance D T where { ...meths for D... }
instance CD T where {}

whereas with (ii) one can write
instance CD T where { ...meths for C...
  ...meths for D... }

I believe that this latter is the sole difference.  Am I right?
[Implementation aspects aside with (i) GHC will pass one dictionary
CD containing a pair of dictionaries, one for C and one for D.]


If so, than rather than invent a whole new mechanism, why not simply
extend the existing superclass mechanism to allow a single instance decl
to declare instances for several classes?  For example, one add to
Haskell 98 the following:
an instance declaration for a class CD with superclasses C and D
may 
give the instances for its superclasses C and D

[One could quibble about details.  E.g Should the class decl for CD
*say* whether the instance decl *must* contain decls for the superclass
methods?  Or can one vary it on a instance-by-instance basis, which
might be more flexible?]


Anyway, my main point it: would a smaller change not suffice?

Simon
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Benjamin Franksen
On Thursday 13 October 2005 12:22, John Meacham wrote:
 On Thu, Oct 13, 2005 at 12:08:27PM +0200, Wolfgang Jeltsch wrote:
   We allow new constructs of this form (the exact syntax is
   flexible of
  
   course):
 class alias (Foo a, Bar a) = FooBar a where
   foo = ...
  
   what this does is declare 'FooBar a' as an alias for the two
   constraints 'Foo a' and 'Bar a'. This affects two things.
 
  Wouldn't it be better to write it this way:
 
  class alias (Foo a, Bar a) = FooBar a where ...
 
  (Foo a, Bar a) = FooBar a normally means that a type is an
  instance of Foo and Bar if it is an instance of FooBar but in the
  case of aliases, a type is also an instance of FooBar if it is an
  instance of Foo and Bar.

 Yeah, I totally agree. it would also reduce confusion with
 superclasses and emphasises the fact that the two sides are
 equivalent everywhere. (except instance heads)

 although perhaps

class alias FooBar a = (Foo a, Bar a)  where ...

 since the new name introduced usually appears to the left of an
 equals sign. This also solves the problems of where to put new
 supertype constraints.

Using '=' instead of '=', you could even leave out the 'alias':

  class FooBar a = (Foo a, Bar a)  where ...

Ben
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Benjamin Franksen
On Thursday 13 October 2005 13:21, Simon Peyton-Jones wrote:
 If so, than rather than invent a whole new mechanism, why not simply
 extend the existing superclass mechanism to allow a single instance
 decl to declare instances for several classes?  For example, one add
 to Haskell 98 the following:
   an instance declaration for a class CD with superclasses C and D
 may
   give the instances for its superclasses C and D

 [One could quibble about details.  E.g Should the class decl for CD
 *say* whether the instance decl *must* contain decls for the
 superclass methods?  Or can one vary it on a instance-by-instance
 basis, which might be more flexible?]

I just want to mention Robert Will's proposal for delayed method 
definitions; see http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/ 
sections 4.3.1 and 4.3.2, which is quite similar to yours.

Cheers,
Ben
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread S.M.Kahrs

 I've considered this before, but never done anything about it because
 superclasses are so close.  Specifically, what is the difference between
 
 (i)   class (C a, D a) = CD a
 and
 (ii)  class alias CD a = (C a, D a)

The difference is that (i) is, in a sense, generative - because
you still have to declare a type to be an instance of CD even if
it is one of both C and D.

That is not only inconvenient it can even create problems,
for modular program development, as class instances always cross
module boundaries [which is a wart].  So if there are two different
modules in your project needing a type to be an instance of CD,
you need to find a single place where to put that instance declaration.

Frankly, as long as there is no way to limit the scope of an instance
it would probably even make sense to treat method-less classes as class
synonyms anyway, i.e. ones that do not require instances.
Though ways of limiting the scope of class instances is probably
a change quite a few people would like to see, so such a change
would inhibit a move in that direction in the future.

Stefan Kahrs
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 12:21:41PM +0100, Simon Peyton-Jones wrote:
 | This is a proposal for a language extension which will hopefully
 mitigate the
 | issues holding back evolution of the standard prelude as well as
 provide
 | useful class abstraction capabilities in general.
 
 A short summary would be type synonyms for class constraints.   You'd
 definitely want the syntax to look as much like a type synonym decl as
 possible.

 I've considered this before, but never done anything about it because
 superclasses are so close.  Specifically, what is the difference between

Actually I think it is pretty orthogonal to superclasses, class aliases
are about composing classes, not building hierarchies.


 
 (i)   class (C a, D a) = CD a
 and
 (ii)  class alias CD a = (C a, D a)
 
 Note that (i) is Haskell 98.
 
 * In both cases one can write
   f :: (CD a) = ...
instead of the more voluminous
   f :: (C a, D a)
 
 * However with (i), for each type T one must write
   instance C T where { ...meths for C... }
   instance D T where { ...meths for D... }
   instance CD T where {}
 
 whereas with (ii) one can write
   instance CD T where { ...meths for C...
 ...meths for D... }
 
 I believe that this latter is the sole difference.  Am I right?

No, there are a number of differences that allow class aliases to be
used for true class abstraction rather than just a shortcut to writing
instances.

 If so, than rather than invent a whole new mechanism, why not simply
 extend the existing superclass mechanism to allow a single instance decl
 to declare instances for several classes?  For example, one add to
 Haskell 98 the following:
   an instance declaration for a class CD with superclasses C and D
 may 
   give the instances for its superclasses C and D

this does not actually solve the problems mentioned in the proposal.

in particular,

(CD a) = a and (C a,D a) = a are distinct types. this means that
you cannot use the aliases as abreviations or alternate names, which is
a very nice side effect. with fine grained class hierarchies, type
signatures get big fast. having a shorthand is very nice.

but worse, it ruins the symmetry. declaring an instance for CD a will
create instances for (C a,D a) but declaring instances  for C a and D a
will not create one for CD. A key point of my design is that you can
declare instances in the new Num hierarchy, or in the haskell 98 one, and
the instances will be propagated both directions. things get much more
complicated when you realize that you might want more than just 2 views
of the same hierarchy and there is not a clear order among them. if you
constantly have to remember to declare instances for the old haskell 98
classes too then there is really no benefit.

Another illustrative example is one that combines aliases with
superclasses.

class alias Num a = Show a = (Additive a, Multiplicative a)

now, Show is a superclass, but Num is an alias for Additive and
Multiplicative. 

if we declare something an instance of Num, we are declaring instances
for precisely Additive and Multiplicative. but not Show, there must already be 
an
existing instance for Show since it is a superclass and not part of the
alias, if this distinction were not made then several bad things happen:

it is obvious you cannot emulate the old haskell 98 behavior and thus
cannot get true abstraction.

declaring an instance for Num where you left out 'show' would rather
than give an error as it should, use the default method for show (which
is undefined). this is definitly what you don't want for Show, but it
might be what you want for an alternate class with a useful default.

with the superclass method you mentioned, how do we control exactly
which classes we are creating instances for? all the way up the
hierarchy back to the base? just one level? neither rules gives us what
we want and if we put that explicitly in the instance declaration we
ruin the whole point of class abstraction. (plus, it seems like the
wrong place to put it anyway). An instance for a class alias always and
exactly declares instances for each of its components and nothing else
and is orthogonal to the superclass hierarchy.


Another key way in which it is different is that it is truely a
composition of classes rather than a ordering on them. with a
superclass relationship, classes are forced to build on top of one
another, you cannot have mutual recursion between class default
methods..

for instance, consider this useful little alias:

class alias EqOrd a = (Eq a, Ord a) where
a == b = compare a b == EQ

now you can declare something as an EqOrd and just provide a 'compare'
method and it will derive everything else including the Eq methods.

notice that the default method is declared the wrong way in the class
hierachy. this is a very handy thing, but is actually necessary to
create the abstraction benefits we want. if we look at the Num example
from my 

RE: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Simon Peyton-Jones
John

Replying just to you to avoid spamming everyone.

| in particular,
| 
| (CD a) = a and (C a,D a) = a are distinct types. this means that
| you cannot use the aliases as abreviations or alternate names, which
is
| a very nice side effect. with fine grained class hierarchies, type
| signatures get big fast. having a shorthand is very nice.

I don't agree.  What do you mean by distinct types?  In H98 both of
these are ok:

f :: CD a = ty
f = ...code...

g :: (C a, D a) = ty
g = f
and
f :: (C a, D a) = ty
f = ...code...

g :: (CD a) = ty
g = f

That is, the two types are interchangeable.

| Another illustrative example is one that combines aliases with
| superclasses.
| 
| class alias Num a = Show a = (Additive a, Multiplicative a)
| 
| now, Show is a superclass, but Num is an alias for Additive and
| Multiplicative.

Yes, this part really confused me.  I didn't understand what it meant.
Here's my attempt to summarise what I think you are proposing.  (This
summary might be useful to add to your note.)

(1a) If I have 
f :: Num a = ...
then I can use any of the class ops of Show, Additive, Multiplicative in
the body of f.

(1b) Dually, a call of f can be satisfied if (Show, Additive,
Multiplicative) are all available (or Num of course).

(2a) I can declare an instance of Num 
* either by giving separate instances for Show, Additive,
Multiplicative; 
* or by giving a separate instance for Show, and an instance for Num
itself

(2b) If a type T is an instance of Additive, then it's an error to also
give a Num instance, even if the instance only gives the methods for
Multiplicative.

(3) In the class decl for Num I can override the default methods for
Additive, Multiplicative.  These new default methods will be used (only)
if I give an instance decl for Num.


Here, (1a,b) are satisfied by H98 superclasses, whereas (2a) and (3) are
not.  Are there any points I've missed in this list?

Simon
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Udo Stenzel
Simon Peyton-Jones wrote:
 I've considered this before, but never done anything about it because
 superclasses are so close.  Specifically, what is the difference between
 
 (i)   class (C a, D a) = CD a
 and
 (ii)  class alias CD a = (C a, D a)
 
 Note that (i) is Haskell 98.

I was about to suggest almost exactly the same.  In particular, John's
proposal could be decomposed into three parts:

1. Allow instance declarations to define methods of superclasses.
   These are simply converted into the appropriate instance declarations
   for the superclasses.

2. Allow class declarations to give defaults for methods in
   superclasses.  Together with (1) they are used in the obvious way.

3. Allow empty instance declarations to be implicitly generated.


As a nice side effect, (1) and (2) together would allow us to cleanly
get rid of the fmap/liftM annoyance:

* class Functor f where { fmap :: ... }
* class Functor m = Monad m where { fmap = liftM }


I'm not sure about (3).  I think, to effectively make Foo a synonym for
Bar, we'd need:

* class Foo a = Bar a
* instance Foo a = Bar a

If the instance for every type were allowed, Foo and Bar would be
indistinguishable from true synonyms.  Further, if classes with no
methods have no use currently, this universal instance could be
compiler generated whenever a class without methods is declared.  Or the
empty class may be treated as a synonym, if that's simpler.  Does this
make any sense?


Udo.


signature.asc
Description: Digital signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Jan-Willem Maessen


On Oct 12, 2005, at 8:00 PM, John Meacham wrote:



[longish proposal for class aliases]



Very nicely done, by the way.



== Notes ==

* class aliases are also able to introduce new superclass  
constraints, such as
  in the Num example we also want to enforce a (Eq a, Show a)  
superclass
  constraint. the interpretation is straightforward, Num in type  
signatures
  expands as if those were part of the alias and when declaring  
instances the
  existence of instances for the superclasses are checked, but not  
filled in
  automatically. I didn't show an example so as to not confuse the  
basic idea
  and because I have not come up with a syntax I am happy with.  
(suggestions

  welcome)



It sounds like there may be a simpler initial extension lurking under  
this, see below.




...
* I had an earlier supertyping proposal you might know about, I  
feel this is
  a much better proposal even though it doesn't fully subsume my  
supertyping
  proposal, I feel it solves the problems it was meant to solve in  
a cleaner

  and easier to implement way.



Having read the previous proposal, I'm inclined to agree.  I feel  
like I can explain this one in a couple of minutes, and the listener  
will be able to figure out most of the subtleties without additional  
help.



* You may wonder why for the num example I put Additive a in the  
class alias

  even though it was already a superclass of AdditiveNegation. that is
  because class aliases do not change the meaning of superclasses,  
you need
  to explicitly list a class if you want instance declarations to  
propagate
  methods to it. superclasses are checked just like normal in class  
aliases.




This is the one possible exception to that.  Again, see below.



* incidental but not earth-shattering benefits include being able to
  declare an instance for a class and all its superclasses at once,
  smarter defaults when you are combining related classes, and much
  nicer type signatures by being able to create your own aliases for
  common combinations of classes.



It seems to me this is a simpler extension here which might serve at  
least as a conceptual stepping-stone to full class aliases---the  
ability to declare an instance for a class and all its superclasses  
at once.  Given that ability, class aliases actually look like a  
relatively simple extension.


One final thing which would be nice is the ability to define  
instances of superclass methods in a subclass declaration.  But this  
takes things in a different direction entirely.


-Jan-Willem Maessen




--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell





___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Paul Govereau
On Oct 12, John Meacham wrote:

 [...]

  class Num a where
  (+), (*):: a - a - a
  (-) :: a - a - a
  negate  :: a - a
  fromInteger :: Integer - a
 
 ideally we would want to split it up like so (but with more mathematically
 precise names):
 
  class Additive a where
(+) :: a - a - a
zero :: a
 
  class Additive a = AdditiveNegation where
  (-) :: a - a - a
  negate  :: a - a
  x - y  = x + negate y
 
  class Multiplicative a where
(*) :: a - a - a
one :: a
 
  class FromInteger a where
  fromInteger  :: Integer - a
 
 [...]
 
  class alias (Addititive a, AdditiveNegation a,
   Multiplicative a, FromInteger a) = Num a where
 one = fromInteger 1
 zero = fromInteger 0
 negate x = zero - x

This class alias isn't 100% backwards compatible, because the original
Num class doesn't have a zero method. For instance, if I had written
this function in my program:

  zero :: Num a = a
  zero = fromInteger 0

Then, after swapping in the new alias, Num, the compiler would
probably complain that I have multiple definitions for zero.

Perhaps there could be a mechanism for hiding class methods as well?
e.g.

class alias (Addititive a without zero,  -- remove zero
 AdditiveNegation a,
 Multiplicative a,
 FromInteger a) = Num a where ...

I am not sure this could still be done with a source-to-source
translation, but perhaps it is worth considering. Of course, if we
allow union and subtraction, then why not addition, intersection,
complement (ok, maybe not complement).

Paul
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 01:41:14PM -0400, Paul Govereau wrote:
 On Oct 12, John Meacham wrote:
 
  [...]
 
   class Num a where
   (+), (*):: a - a - a
   (-) :: a - a - a
   negate  :: a - a
   fromInteger :: Integer - a
  
  ideally we would want to split it up like so (but with more mathematically
  precise names):
  
   class Additive a where
 (+) :: a - a - a
 zero :: a
  
   class Additive a = AdditiveNegation where
   (-) :: a - a - a
   negate  :: a - a
   x - y  = x + negate y
  
   class Multiplicative a where
 (*) :: a - a - a
 one :: a
  
   class FromInteger a where
   fromInteger  :: Integer - a
  
  [...]
  
   class alias (Addititive a, AdditiveNegation a,
Multiplicative a, FromInteger a) = Num a where
  one = fromInteger 1
  zero = fromInteger 0
  negate x = zero - x
 
 This class alias isn't 100% backwards compatible, because the original
 Num class doesn't have a zero method. For instance, if I had written
 this function in my program:
 
   zero :: Num a = a
   zero = fromInteger 0
 
 Then, after swapping in the new alias, Num, the compiler would
 probably complain that I have multiple definitions for zero.

You would use the module system to hide these extra methods.. like your
prelude lookalike will have

module Prelude(Num(negate,(-),(+),(*),fromInteger), ...) where  

and NewPrelude would export everything.


 Perhaps there could be a mechanism for hiding class methods as well?
 e.g.
 
 class alias (Addititive a without zero,  -- remove zero
  AdditiveNegation a,
  Multiplicative a,
  FromInteger a) = Num a where ...
 
 I am not sure this could still be done with a source-to-source
 translation, but perhaps it is worth considering. Of course, if we
 allow union and subtraction, then why not addition, intersection,
 complement (ok, maybe not complement).

no need, the module system lets us hide what we need to to keep
compatability and is not tied to the alias itself, which is good
because some people might want to use one and zero with Num and import
the appropriate module to let them do that.
John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 01:46:14PM +0200, Benjamin Franksen wrote:
 Using '=' instead of '=', you could even leave out the 'alias':
 
   class FooBar a = (Foo a, Bar a)  where ...

true. for the purposes of discussion I think I will keep using the
'alias' so it is clearer what is going on. but if it were actually
implemented we could decide whether we want it or not.
John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread John Meacham
On Thu, Oct 13, 2005 at 10:18:24AM -0400, Jan-Willem Maessen wrote:
 * incidental but not earth-shattering benefits include being able to
   declare an instance for a class and all its superclasses at once,
   smarter defaults when you are combining related classes, and much
   nicer type signatures by being able to create your own aliases for
   common combinations of classes.
 
 
 It seems to me this is a simpler extension here which might serve at  
 least as a conceptual stepping-stone to full class aliases---the  
 ability to declare an instance for a class and all its superclasses  
 at once.  Given that ability, class aliases actually look like a  
 relatively simple extension.

Yeah, see my response to SPJ for why this doesn't quite solve all the
problems mentioned.

the gist of the main one is how do you control which instances you are
creating? surely you don't want someone declaring an instance of Num to
fill in Eq and Show with defaults (bottom and a different kind of bottom
respectivly), but there are often cases where you _do_ want the
defaults. if you only have it fill in non-existing instances then
importing a module could silently change the behavior of code as it
might bring in an instance for something you wanted to use the default
methods for. All in all, it seems like a can of worms and implementing
full class aliases is of roughly the same amount of work.

there are a few other issues mentioned in my other reply.

 
 One final thing which would be nice is the ability to define  
 instances of superclass methods in a subclass declaration.  But this  
 takes things in a different direction entirely.

I am not sure what you mean by this?

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread David Menendez
Udo Stenzel writes:

 Simon Peyton-Jones wrote:
  I've considered this before, but never done anything about it
  because superclasses are so close.  Specifically, what is the
  difference between
  
  (i) class (C a, D a) = CD a
  and
  (ii)class alias CD a = (C a, D a)
  
  Note that (i) is Haskell 98.
 
 I was about to suggest almost exactly the same.  In particular, John's
 proposal could be decomposed into three parts:
 
 1. Allow instance declarations to define methods of superclasses.
These are simply converted into the appropriate instance 
declarations for the superclasses.
 
 2. Allow class declarations to give defaults for methods in
superclasses.  Together with (1) they are used in the obvious way.
 
 3. Allow empty instance declarations to be implicitly generated.
 
 
 As a nice side effect, (1) and (2) together would allow us to cleanly
 get rid of the fmap/liftM annoyance:
 
 * class Functor f where { fmap :: ... }
 * class Functor m = Monad m where { fmap = liftM }

This can also get us into trouble. Consider,

class Functor f where fmap :: ...
class Functor m = Monad m where { fmap = liftM; ... }
class Functor d = Comonad d where { fmap = liftD; ... }

The Id functor is an instance of Monad and Comonad; what happens to the
fmap definition?

 If the instance for every type were allowed, Foo and Bar would be
 indistinguishable from true synonyms.  Further, if classes with no
 methods have no use currently, this universal instance could be
 compiler generated whenever a class without methods is declared.  Or 
 the empty class may be treated as a synonym, if that's simpler.  Does 
 this make any sense?

I don't know that method-less classes have *no* value. You could use
them to make additional claims about a type. For example,

class Monoid m where { ... }

class CommutativeMonoid m where {}

The idea being that instances of CommutativeMonoid satisfy additional
laws.
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] PROPOSAL: class aliases (revised)

2005-10-13 Thread John Meacham
I have revised the proposal and put it on the web here:

 http://repetae.net/john/recent/out/classalias.html

changes include a new, clearer syntax, some typo fixes, and a new
section describing how class aliases interact with superclasses.

I will update that web page with any new devolpments.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread ajb
G'day all.

Quoting Simon Peyton-Jones [EMAIL PROTECTED]:

 I've considered this before, but never done anything about it because
 superclasses are so close.  Specifically, what is the difference between

 (i)   class (C a, D a) = CD a
 and
 (ii)  class alias CD a = (C a, D a)

 Note that (i) is Haskell 98.

To be a true typeclass synonym, there would also be an implied default
instance:

class (C a, D a) = CD a
instance (C a, D a) = CD a

...and this is not Haskell 98.

Cheers,
Andrew Bromage
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] PROPOSAL: class aliases

2005-10-12 Thread John Meacham

= Class Aliases =

This is a proposal for a language extension which will hopefully mitigate the
issues holding back evolution of the standard prelude as well as provide
useful class abstraction capabilities in general.

It's main goals are to

* remove the false tension between the granularity of a class hierarchy and
  its practical usability.

* Allow one to modify a class hierarchy while retaining 100% backwards
  compatibility with a class API. with a specific use being able to replace
  the prelude's numeric hierarchy while retaining full haskell 98 compatibility,
  including the fact that libraries that only know about haskell 98 will have
  their instances automatically propagated to the new class hierarchy (and
  vice versa), so switching over can be fully incremental.

* allow one to provide simple and advanced interfaces to a class hierarchy,
  much as one can do with function libraries.

* it incidentally allows certain things that have been requested on the list
  as 'nice to have' but not world shattering.

* not interfere with separate compilation and be describable by a
  straightforward source-source translation.

feel free to skip the next section if you know the issues involved in
replacing the numeric hierarchy of the prelude transparently :) This
specification is meant to be informal but precise and complete. if any
of the translation rules are unclear, then let me know.

== The Problem ==

Many alternate preludes have been proposed, however to date none have gained
popularity beyond the extensions to the standard libraries provided by
fptools. Since as a general rule, the haskell community only likes to
standardize changes that have been actively used and implemented already (a
very good policy) this makes evolution of the standard problematic.

Although it is easy enough to provide new functions and datatypes, providing
wrapper routines with the old interfaces to allow incremental use of a new
prelude or any library. there is no way to hide the fact that you changed a
class hierarchy. if you split a class into two, every instance has to change,
even if the split is irrelevant to a given datatype. Furthermore, depending
on how you split or join classes, many type signatures will have to be
rewritten. Since Haskell projects tend to be amalgamations of many different
libraries and code from previous projects, this makes using alternate
preludes with anything larger than a toy project unpossible.

The problem is compounded when you consider the fact that we ideally want
multiple competing preludes or certainly different versions of the same one.
Imagine a library that provides a handy new Numeric datatype. the writer of
the library only knows about the main prelude and doesn't concern himself with
the various experimental preludes out there so declares an instance for Num.
Bill comes along and realizes he needs an instance for the new Prelude so
declares it an instance of ExperimentalNum, Phil, who also uses the library
and the new experimental prelude needs to declare his own ExperimentalNum
instance. suddenly Bill's and Phil's libraries cannot be combined by Susan who
just wants to get work done and needs both Bill's and Phil's libraries.

The basic issue is that you end up with a quadratic number of instances for
every datatype combined with every alternative prelude and it is not clear who
should be providing these instances. every library writer should not need to
know about every alternate prelude out there and vice versa. Not only that
but most of the instances will be very redundant, ExperimentalNum and Num
most likely provide many of the same operations, you should only need to
declare an instance for one and have it automatically propegated to the other.


== The Extension ==

In haskell, you may create abstract data types, where you are free to change
the internal representation without affecting the visible interface, you may
create function impedance matching libraries, providing alternate interfaces
to the same functionality. however, there is no way to abstract your class
hiearchy. there is no way to hide your class layout in such a way you can
change it behind the scenes, once a sizable codebase is built up expecting a
certain class layout, there is no incremental migration path to something 
better.

This extension allows the creation of class aliases, or effectively different
views of the class hierarchy. this allows library writers to change the class
hierarchy under the hood without affecting the visible interface as well as
providing cleaner interfaces to begin with, hiding unimportant implementation
details of how the classes are laid out from regular users, while providing
the more advanced interfaces to power users.

This extension may be carried out completely in the front end via a
source-source translation and does not inhibit separate compilation.

given

  class Foo a where
foo :: a - Bool
foo x = False

  class Bar b where
bar :: Int - b - [b]


Re: [Haskell] PROPOSAL: class aliases

2005-10-12 Thread Philippa Cowderoy

On Wed, 12 Oct 2005, John Meacham wrote:


ideally we would want to split it up like so (but with more mathematically
precise names):



Might it also be reasonable to provide less mathematical names for some 
classes, and possibly allow users to let the compiler know which ones they 
find more readable? A lot of users would find Mappable more intuitive than 
Functor for example, and the improved error messages might make it more 
practical to call fmap map again.


--
[EMAIL PROTECTED]

Ivanova is always right. 
I will listen to Ivanova. 
I will not ignore Ivanova's recomendations. 
Ivanova is God. 
And, if this ever happens again, Ivanova will personally rip your lungs out!

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] PROPOSAL: class aliases

2005-10-12 Thread John Meacham
On Thu, Oct 13, 2005 at 01:14:19AM +0100, Philippa Cowderoy wrote:
 On Wed, 12 Oct 2005, John Meacham wrote:
 
 ideally we would want to split it up like so (but with more mathematically
 precise names):
 
 
 Might it also be reasonable to provide less mathematical names for some 
 classes, and possibly allow users to let the compiler know which ones they 
 find more readable? A lot of users would find Mappable more intuitive than 
 Functor for example, and the improved error messages might make it more 
 practical to call fmap map again.

class aliases help this too :)

class alias Functor m = Mappable m

oh.. or 

class alias (Monad m, Functor m) = Monad' m where
fmap = liftM

now you can just change your 
instance Monad to instance Monad' and you get your functor instance for
free..

I hadn't thought about that one. (which has bugged me a lot before)
John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell