Re: A question about run-time errors when class members are undefined

We are adding classes and instances to Helium.
We wondered about the aspect that it is allowed to have a class instance
of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink? Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class. I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do: class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods: * the need to provide an overloading for every method, even though it may not make sense (or suffer a run-time error, as you say) * the inability to 'fine tune' methods for a specific datatype [**] * an internal compiler/object code cost of passing a group of methods in a dictionary as tuple (as apposed to directly selecting a single method) [**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense. If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose. So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==) show @Int = primShowInt -- in effect pattern matching on the type (==) @Int = primEqInt -- so see showList below That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature: show @a :: a -> String -- compare show :: Show a => a -> String (==) @a :: a -> a -> Bool Non-overladable functions don't have `@a` to the left of `::`. How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`: show @a :: showsPrec @a => a -> String -- supermethod constraint show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint => show @[a] xss = showList xss (*) @a :: (+) @a => a -> a -> a Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes. http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt It reviews several possible designs, but not all those possibilities made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes: square x = x * x -- no explicit signature given square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded rms = sqrt . square -- no explicit signature rms :: sqrt @a => a -> a -- signature inferred Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
... a run-time error results.
Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance. Altogether, I'd say, the culprit is the strong bias in early Haskell to bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level? AntC

Hi Anthony, We first go the slavish route, to provide a basis for changing things later. So I am not looking for alternative ways of doing this, I am just wondering whether there is a rationale for doing things this way. The document does not give one. And now I hear that records suffer from the same issue (thanks Cale). We had not run into this yet, because right now Helium does not have ‘em. Both sound fishy to me and if nobody can make a case for having things this way in the first place, I wonder why it’s like that. Adding associated types is a long way off, or any such language extensions is at this point. The only one I might consider at this time is GADTs, but only if I find a master student to investigate type error diagnosis in that setting. Jur
On 4Oct, 2018, at 03:55, Anthony Clayden
wrote: We are adding classes and instances to Helium. We wondered about the aspect that it is allowed to have a class instance of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink?
Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class.
I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do:
class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a
Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods: * the need to provide an overloading for every method, even though it may not make sense (or suffer a run-time error, as you say) * the inability to 'fine tune' methods for a specific datatype [**] * an internal compiler/object code cost of passing a group of methods in a dictionary as tuple (as apposed to directly selecting a single method)
[**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense.
If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose.
So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==)
show @Int = primShowInt -- in effect pattern matching on the type (==) @Int = primEqInt -- so see showList below That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature:
show @a :: a -> String -- compare show :: Show a => a -> String (==) @a :: a -> a -> Bool Non-overladable functions don't have `@a` to the left of `::`. How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`:
show @a :: showsPrec @a => a -> String -- supermethod constraint show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint => show @[a] xss = showList xss (*) @a :: (+) @a => a -> a -> a
Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes. http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt
It reviews several possible designs, but not all those possibilities made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes:
square x = x * x -- no explicit signature given square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded rms = sqrt . square -- no explicit signature rms :: sqrt @a => a -> a -- signature inferred
Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
... a run-time error results.
Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance.
Altogether, I'd say, the culprit is the strong bias in early Haskell to bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level?
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

On Fri, 5 Oct 2018 at 9:00 PM, Jurriaan Hage
We first go the slavish route, to provide a basis for changing things later.
So I am not looking for alternative ways of doing this, I am just wondering whether there is a rationale for doing things this way. The document does not give one.
The only explanation I can think of is that there might be default implementations of the methods -- very likely defined in terms of other methods in the class. (Such as (/=) defaulting to `not (==)`, and (==) defaulting to `not (/=)`.) Then it's a nuisance to have to say 'just use the default'. But I agree GHC should cope better than a run-time exception.
And now I hear that records suffer from the same issue (thanks Cale).
I'm not perturbed or surprised by that. Consider the assignments to the `zn` have the same effect here: data D = MkD {x :: Int, y :: Bool} z1 = MkD{ x = 5 } -- y not mentioned, so set undefined z2 = MkD{ x = 5, y = undefined } z3 = MkD 5 undefined We had not run into this yet, because right now Helium does not have ‘em. Haskell records were embarrassingly bad in 1998. No change or improvement in Haskell 2010. Some minor easing in recent years with GHC extensions -- I'd call that lipstick on a pig. If you've not implemented 'em yet, I just plain wouldn't. Ever. Support Lenses or any of the 50 gazillion proposals. Even Hugs' TRex is better (throws a type error at compile time if you omit a field). Both sound fishy to me and if nobody can make a case for having things this
way in the first place, I wonder why it’s like that.
There's a huge volume of minor inconsistencies and annoyances in GHC. I guess we hardly notice because we get used to them (or we each use a subset of features). A lot can be explained by the shackle of backwards compatibility: every new extension must use distinct syntax, so that people who don't want it/aren't aware of it don't run into surprises. For example, there's now annoyingly similar-but-different semantics for H98 data, existential fields, constrained fields, GADTs, data families/instances, view patterns, pattern synonyms. I can't help but feel they should all get unified into a single semantics; then those differing syntactic forms be treated as shorthands/variations on a theme.
The only one I might consider at this time is GADTs,
I do find the (~) type equality constraints from GADTs/Type Families very pleasing and intuitive. You might be able to implement that without all the other paraphernalia. AntC
On 4Oct, 2018, at 03:55, Anthony Clayden
wrote: We are adding classes and instances to Helium. We wondered about the aspect that it is allowed to have a class instance of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink?
Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class.
I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do:
class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a
Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods: * the need to provide an overloading for every method, even though it may not make sense (or suffer a run-time error, as you say) * the inability to 'fine tune' methods for a specific datatype [**] * an internal compiler/object code cost of passing a group of methods in a dictionary as tuple (as apposed to directly selecting a single method)
[**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense.
If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose.
So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==)
show @Int = primShowInt -- in effect pattern matching on the type (==) @Int = primEqInt -- so see showList below That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature:
show @a :: a -> String -- compare show :: Show a => a -> String (==) @a :: a -> a -> Bool Non-overladable functions don't have `@a` to the left of `::`. How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`:
show @a :: showsPrec @a => a -> String -- supermethod constraint show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint => show @[a] xss = showList xss (*) @a :: (+) @a => a -> a -> a
Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes.
http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt
It reviews several possible designs, but not all those possibilities
made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes:
square x = x * x -- no explicit signature
square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded rms = sqrt . square -- no explicit signature rms :: sqrt @a => a -> a -- signature inferred
Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
... a run-time error results.
Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale
given points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance.
Altogether, I'd say, the culprit is the strong bias in early Haskell to
bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level?
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

On Fri, 5 Oct 2018 at 9:00 PM, Jurriaan Hage
We first go the slavish route, to provide a basis for changing things later.
Ah. That comment seemed strange, but I've just read up on Helium: you're aiming to provide a beginners' environment for Haskell. Then without type classes, I'm wondering what Helium is doing now for arithmetic or equality-testing or show or read? Do you mean you've somehow 'faked' the Prelude classes, but don't yet allow programmers to declare their own classes/instances? Being able to declare your own datatypes without writing instances for them seems particularly awkward. If Helium essentially supports less than H98, I'm wondering why you didn't start with Hugs, and work on it giving better error messages? I'm finding Hugs very easy to hack; the messages are particularly easy to work with. (OK it's written in C++, but the 'interesting' parts are just function calls, so the host language seems irrelevant.) AntC

Hi everyone, IIRC one of the arguments against having many separate classes is that a class is not a just set of methods, it's also the relations between them, such as the important laws between `return` and `>>=`. And then for example a class with just `return` doesn't give any information what `return x` means or what should be its properties. That said, one of really painful points of Haskell is that refactoring a hierarchy of type-classes means breaking all the code that implements them. This was also one of the main reasons why reason making Applicative a superclass of Monad took so long. It'd be much nicer to design type-classes in such a way that an implementation doesn't have to really care about the exact hierarchy. The Go language takes a very simple view on this: A type implements an interface if all the methods are implemented, without having to explicitly specify this intent [1]. This looks very nice and clean indeed. But the drawback is that this further decouples type-classes (interfaces) from their laws (like monad laws, monoid laws etc.). For example, in Haskell we could have class (Return m, Bind m) => Monad m where without any methods specified. But instances of `Monad` should be only such types for which `return` and `>>=` satisfy the monad laws. And this would distinguish them from types that have both `Return` and `Bind` instances, but don't satisfy the laws. Unfortunately I'm not sure if there is a good solution for achieving both these directions. [1] https://tour.golang.org/methods/10 Cheers, Petr čt 4. 10. 2018 v 3:56 odesílatel Anthony Clayden < anthony_clayden@clear.net.nz> napsal:
We are adding classes and instances to Helium.
We wondered about the aspect that it is allowed to have a class instance
of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink?
Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class.
I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do:
class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a
Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods:
* the need to provide an overloading for every method, even though it may not make sense
(or suffer a run-time error, as you say)
* the inability to 'fine tune' methods for a specific datatype [**]
* an internal compiler/object code cost of passing a group of methods in a dictionary as tuple
(as apposed to directly selecting a single method)
[**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense.
If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose.
So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==)
show @Int = primShowInt -- in effect pattern matching on the type
(==) @Int = primEqInt -- so see showList below
That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature:
show @a :: a -> String -- compare show :: Show a => a -> String
(==) @a :: a -> a -> Bool
Non-overladable functions don't have `@a` to the left of `::`.
How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`:
show @a :: showsPrec @a => a -> String -- supermethod constraint
show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint =>
show @[a] xss = showList xss
(*) @a :: (+) @a => a -> a -> a
Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes. http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt
It reviews several possible designs, but not all those possibilities made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes:
square x = x * x -- no explicit signature given
square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded
rms = sqrt . square -- no explicit signature
rms :: sqrt @a => a -> a -- signature inferred
Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
... a run-time error results.
Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance.
Altogether, I'd say, the culprit is the strong bias in early Haskell to bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level?
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

On Sat, 6 Oct 2018 at 9:47 AM, Petr Pudlák
IIRC one of the arguments against having many separate classes is that a class is not a just set of methods, it's also the relations between them,
Hi Petr, I was talking about splitting out Haskell's current class hierarchy as a step towards doing away with classes altogether. If your language insists on methods being held in classes, that's just tedious bureacracy to invent class names. The relations between classes (including between single-method classes) can be captured through superclass constraints. For example, in the Haskell 2010 report class (Eq a, Show a) => Num a where ... such as the important laws between `return` and `>>=`. And then for example
a class with just `return` doesn't give any information what `return x` means or what should be its properties.
Then make Bind a superclass constraint on `return` (or vice versa, or both ways). Just as the laws for Num's methods are defined in terms of equality x + negate x == fromInteger 0 -- for example Talking about laws is a red herring: you can't declare the laws/the compiler doesn't enforce them or rely on them in any way. Indeed the Lensaholics seem to take pleasure in building lenses that break the (van Laarhoven) laws.
That said, one of really painful points of Haskell is that refactoring a hierarchy of type-classes means breaking all the code that implements them. This was also one of the main reasons why reason making Applicative a superclass of Monad took so long. It'd be much nicer to design type-classes in such a way that an implementation doesn't have to really care about the exact hierarchy.
Yes that's what I was saying. Unfortunately for Haskell's Num class, I think it's just too hard. So a new language has an opportunity to avoid that. If OTOH Helium wants to slavishly follow Haskell, I'm wondering what is the point of Helium. With Applicative, IIRC, refactoring had to wait until we got Constraint kinds and type families that could produce them. Would Helium want to put all that into a language aimed at beginners? For example, in Haskell we could have
class (Return m, Bind m) => Monad m where
without any methods specified. But instances of `Monad` should be only such types for which `return` and `>>=` satisfy the monad laws.
First: what does "satisfy the xxx laws" mean? The Haskell report and GHC's Prelude documentation state a bunch of laws; and it's a good discipline to write down laws if you're creating a class; but it's only documentation. Arguably IO, the most commonly used Monad, breaks the Monad laws in rather serious ways because it imposes sequence of execution; and it would be unfit for purpose if it were pure/lazy function application. Then: what do you think a language could do to detect if some instance satisfies the laws? (Even supposing you could declare them.) And this would distinguish them from types that have both `Return` and
`Bind` instances, but don't satisfy the laws.
You could have distinct classes/distinct operators. Oh, but then `do` dotation would break.
Unfortunately I'm not sure if there is a good solution for achieving both these directions.
I don't think there's any solution for achieving "satisfy the xxx laws". AntC
čt 4. 10. 2018 v 3:56 odesílatel Anthony Clayden < anthony_clayden@clear.net.nz> napsal:
We are adding classes and instances to Helium.
We wondered about the aspect that it is allowed to have a class instance
of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink?
Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class.
I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do:
class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a
Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods:
* the need to provide an overloading for every method, even though it may not make sense
(or suffer a run-time error, as you say)
* the inability to 'fine tune' methods for a specific datatype [**]
* an internal compiler/object code cost of passing a group of methods in a dictionary as tuple
(as apposed to directly selecting a single method)
[**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense.
If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose.
So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==)
show @Int = primShowInt -- in effect pattern matching on the type
(==) @Int = primEqInt -- so see showList below
That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature:
show @a :: a -> String -- compare show :: Show a => a -> String
(==) @a :: a -> a -> Bool
Non-overladable functions don't have `@a` to the left of `::`.
How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`:
show @a :: showsPrec @a => a -> String -- supermethod constraint
show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint =>
show @[a] xss = showList xss
(*) @a :: (+) @a => a -> a -> a
Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes. http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt
It reviews several possible designs, but not all those possibilities made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes:
square x = x * x -- no explicit signature given
square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded
rms = sqrt . square -- no explicit signature
rms :: sqrt @a => a -> a -- signature inferred
Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
... a run-time error results.
Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance.
Altogether, I'd say, the culprit is the strong bias in early Haskell to bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level?
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

You're implicitly arguing that no language should have support for declaring informal intentions. That's rather more controversial than you might think and it's worth separating out as a subject. The fact you cheerfully talk about making return and bind inherently related via superclass constraints is pretty suggestive. Away from monads, there are a lot of other uses for return-like behaviour that have a different (if often-related) set of laws. Which is exactly why many people want them to be completely separate superclasses of Monad. It's only when they're used to form a monad that those extra laws show up. Which no, Haskell can't enforce, but there's a big difference between "this breaks because seq in a partial language weirds things" and "this would be broken in a total setting too". What happens when I legitimately want both operations but a different set of laws, and don't want my stuff being passed to things that reasonably expect the monad laws to hold? Asking a researcher who's producing actual results "what's the point?" is more than a little inflammatory, too. Helium is not accountable to us. On 06/10/2018 04:18, Anthony Clayden wrote:
On Sat, 6 Oct 2018 at 9:47 AM, Petr Pudlák
mailto:redirect@vodafone.co.nz> wrote: IIRC one of the arguments against having many separate classes is that a class is not a just set of methods, it's also the relations between them,
Hi Petr, I was talking about splitting out Haskell's current class hierarchy as a step towards doing away with classes altogether. If your language insists on methods being held in classes, that's just tedious bureacracy to invent class names.
The relations between classes (including between single-method classes) can be captured through superclass constraints. For example, in the Haskell 2010 report
class (Eq a, Show a) => Num a where ...
such as the important laws between `return` and `>>=`. And then for example a class with just `return` doesn't give any information what `return x` means or what should be its properties.
Then make Bind a superclass constraint on `return` (or vice versa, or both ways).
Just as the laws for Num's methods are defined in terms of equality
x + negate x == fromInteger 0 -- for example
Talking about laws is a red herring: you can't declare the laws/the compiler doesn't enforce them or rely on them in any way. Indeed the Lensaholics seem to take pleasure in building lenses that break the (van Laarhoven) laws.
That said, one of really painful points of Haskell is that refactoring a hierarchy of type-classes means breaking all the code that implements them. This was also one of the main reasons why reason making Applicative a superclass of Monad took so long. It'd be much nicer to design type-classes in such a way that an implementation doesn't have to really care about the exact hierarchy.
Yes that's what I was saying. Unfortunately for Haskell's Num class, I think it's just too hard. So a new language has an opportunity to avoid that. If OTOH Helium wants to slavishly follow Haskell, I'm wondering what is the point of Helium.
With Applicative, IIRC, refactoring had to wait until we got Constraint kinds and type families that could produce them. Would Helium want to put all that into a language aimed at beginners?
For example, in Haskell we could have
class (Return m, Bind m) => Monad m where
without any methods specified. But instances of `Monad` should be only such types for which `return` and `>>=` satisfy the monad laws.
First: what does "satisfy the xxx laws" mean? The Haskell report and GHC's Prelude documentation state a bunch of laws; and it's a good discipline to write down laws if you're creating a class; but it's only documentation. Arguably IO, the most commonly used Monad, breaks the Monad laws in rather serious ways because it imposes sequence of execution; and it would be unfit for purpose if it were pure/lazy function application.
Then: what do you think a language could do to detect if some instance satisfies the laws? (Even supposing you could declare them.)
And this would distinguish them from types that have both `Return` and `Bind` instances, but don't satisfy the laws.
You could have distinct classes/distinct operators. Oh, but then `do` dotation would break.
Unfortunately I'm not sure if there is a good solution for achieving both these directions.
I don't think there's any solution for achieving "satisfy the xxx laws".
AntC
čt 4. 10. 2018 v 3:56 odesílatel Anthony Clayden
mailto:anthony_clayden@clear.net.nz> napsal: > We are adding classes and instances to Helium.
> We wondered about the aspect that it is allowed to have a class instance
> of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink?
Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class.
I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do:
class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a
Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods:
* the need to provide an overloading for every method, even though it may not make sense
(or suffer a run-time error, as you say)
* the inability to 'fine tune' methods for a specific datatype [**]
* an internal compiler/object code cost of passing a group of methods in a dictionary as tuple
(as apposed to directly selecting a single method)
[**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense.
If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose.
So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==)
show @Int = primShowInt -- in effect pattern matching on the type
(==) @Int = primEqInt -- so see showList below
That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature:
show @a :: a -> String -- compare show :: Show a => a -> String
(==) @a :: a -> a -> Bool
Non-overladable functions don't have `@a` to the left of `::`.
How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`:
show @a :: showsPrec @a => a -> String -- supermethod constraint
show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint =>
show @[a] xss = showList xss
(*) @a :: (+) @a => a -> a -> a
Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes. http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt
It reviews several possible designs, but not all those possibilities made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes:
square x = x * x -- no explicit signature given
square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded
rms = sqrt . square -- no explicit signature
rms :: sqrt @a => a -> a -- signature inferred
Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
> ... a run-time error results. > > Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance.
Altogether, I'd say, the culprit is the strong bias in early Haskell to bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level?
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org mailto:Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

Anthony
You may be interested in Carlos Camarao’s interesting work. For a long time now he has advocated (in effect) making each function into its own type class, rather that grouping them into classes. Perhaps that is in line with your thinking.
https://homepages.dcc.ufmg.br/~camarao/
Simon
From: Haskell-prime
We are adding classes and instances to Helium.
We wondered about the aspect that it is allowed to have a class instance
of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink? Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class. I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do: class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods: * the need to provide an overloading for every method, even though it may not make sense (or suffer a run-time error, as you say) * the inability to 'fine tune' methods for a specific datatype [**] * an internal compiler/object code cost of passing a group of methods in a dictionary as tuple (as apposed to directly selecting a single method) [**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense. If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose. So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==) show @Int = primShowInt -- in effect pattern matching on the type (==) @Int = primEqInt -- so see showList below That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature: show @a :: a -> String -- compare show :: Show a => a -> String (==) @a :: a -> a -> Bool Non-overladable functions don't have `@a` to the left of `::`. How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`: show @a :: showsPrec @a => a -> String -- supermethod constraint show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint => show @[a] xss = showList xss (*) @a :: (+) @a => a -> a -> a Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes. http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txthttps://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fhomepages.inf.ed.ac.uk%2Fwadler%2Fpapers%2Fclass-letter%2Fclass-letter.txt&data=02%7C01%7Csimonpj%40microsoft.com%7C5ec7c3a23a9746bb154b08d62b3a7ba2%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636743927613528630&sdata=vXgR1YLqw8ERzEbhVZBGr%2FpB5fMLMmYtnwt6Bpp4wGs%3D&reserved=0 It reviews several possible designs, but not all those possibilities made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes: square x = x * x -- no explicit signature given square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded rms = sqrt . square -- no explicit signature rms :: sqrt @a => a -> a -- signature inferred Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
... a run-time error results.
Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance. Altogether, I'd say, the culprit is the strong bias in early Haskell to bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level? AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.orgmailto:Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-primehttps://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fhaskell-prime&data=02%7C01%7Csimonpj%40microsoft.com%7C5ec7c3a23a9746bb154b08d62b3a7ba2%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636743927613528630&sdata=%2FVDtNLEzevef69Qs9rzrd5V2lBJzMLjRAxBBYvbsPAs%3D&reserved=0

On Mon, 8 Oct 2018 at 8:41 PM, Simon Peyton Jones wrote: You may be interested in Carlos Camarao’s interesting work. For a long
time now he has advocated (in effect) making each function into its own type class, rather that grouping them into classes.
No I think you're mis-apprehending. From the abstract to the group's SBLP2016 paper: "This depends on a modularization of instance visibility, as well as on a redefinition of Haskell’s ambiguity rule." You might remember early last year Carlos submitted a proposal (in two rounds). Your comments were very relevant https://github.com/ghc-proposals/ghc-proposals/pull/48#issuecomment-28712400... Relevant because not just was it difficult to understand the proposal, the proposal had no answer to how instance resolution was to behave. "expression ambiguity" turned out to mean: use module scope to resolve overloading. In the second round of the proposal and in an extended email exchange off-forum with (I think it was) Rodrigo Ribeiro in Carlos' group I tried to tease out how module-scoped instances were going to work for a method exported to a module where there was a different instance in scope. Of course 'orphan instances' are the familiar symptom in GHC. Wadler & Blott's 1988 paper last paragraph had already explained: "But there is no principal type! " Perhaps that is in line with your thinking.
Not at all. My thinking is coming directly from Wadler's early 1988 memo
that I referenced (note *not* the W&B paper) + using some of GHC's more
recent features like explicit type application in terms; and its
counterpart: explicit method application in types.
I wonder how different would have been the history of Haskell if Wadler had
not borrowed the terminology "class" and "method". Since Helium has a focus
on Haskell learners/beginners: I wonder how much confusion we might have
saved those coming from OOP where the terms mean something really quite
different. We might have avoided "class" altogether; and talked of
"overloaded function".
AntC
*From:* Haskell-prime
Clayden *Sent:* 06 October 2018 04:19 *To:* Petr Pudlák
*Cc:* haskell-prime@haskell.org *Subject:* Re: A question about run-time errors when class members are undefined On Sat, 6 Oct 2018 at 9:47 AM, Petr Pudlák
wrote: IIRC one of the arguments against having many separate classes is that a class is not a just set of methods, it's also the relations between them,
Hi Petr, I was talking about splitting out Haskell's current class hierarchy as a step towards doing away with classes altogether. If your language insists on methods being held in classes, that's just tedious bureacracy to invent class names.
The relations between classes (including between single-method classes) can be captured through superclass constraints. For example, in the Haskell 2010 report
class (Eq a, Show a) => Num a where ...
such as the important laws between `return` and `>>=`. And then for example a class with just `return` doesn't give any information what `return x` means or what should be its properties.
Then make Bind a superclass constraint on `return` (or vice versa, or both ways).
Just as the laws for Num's methods are defined in terms of equality
x + negate x == fromInteger 0 -- for example
Talking about laws is a red herring: you can't declare the laws/the compiler doesn't enforce them or rely on them in any way. Indeed the Lensaholics seem to take pleasure in building lenses that break the (van Laarhoven) laws.
That said, one of really painful points of Haskell is that refactoring a hierarchy of type-classes means breaking all the code that implements them. This was also one of the main reasons why reason making Applicative a superclass of Monad took so long. It'd be much nicer to design type-classes in such a way that an implementation doesn't have to really care about the exact hierarchy.
Yes that's what I was saying. Unfortunately for Haskell's Num class, I think it's just too hard. So a new language has an opportunity to avoid that. If OTOH Helium wants to slavishly follow Haskell, I'm wondering what is the point of Helium.
With Applicative, IIRC, refactoring had to wait until we got Constraint kinds and type families that could produce them. Would Helium want to put all that into a language aimed at beginners?
For example, in Haskell we could have
class (Return m, Bind m) => Monad m where
without any methods specified. But instances of `Monad` should be only such types for which `return` and `>>=` satisfy the monad laws.
First: what does "satisfy the xxx laws" mean? The Haskell report and GHC's Prelude documentation state a bunch of laws; and it's a good discipline to write down laws if you're creating a class; but it's only documentation. Arguably IO, the most commonly used Monad, breaks the Monad laws in rather serious ways because it imposes sequence of execution; and it would be unfit for purpose if it were pure/lazy function application.
Then: what do you think a language could do to detect if some instance satisfies the laws? (Even supposing you could declare them.)
And this would distinguish them from types that have both `Return` and `Bind` instances, but don't satisfy the laws.
You could have distinct classes/distinct operators. Oh, but then `do` dotation would break.
Unfortunately I'm not sure if there is a good solution for achieving both these directions.
I don't think there's any solution for achieving "satisfy the xxx laws".
AntC
čt 4. 10. 2018 v 3:56 odesílatel Anthony Clayden < anthony_clayden@clear.net.nz> napsal:
We are adding classes and instances to Helium.
We wondered about the aspect that it is allowed to have a class instance
of which not all fields have a piece of code/value associated with them, ...
I have a suggestion for that. But first let me understand where you're going with Helium. Are you aiming to slavishly reproduce Haskell's classes/instances, or is this a chance for a rethink?
Will you want to include associated types and associated datatypes in the classes? Note those are just syntactic sugar for top-level type families and data families. It does aid readability to put them within the class.
I would certainly rethink the current grouping of methods into classes. Number purists have long wanted to split class Num into Additive vs Multiplicative. (Additive would be a superclass of Multiplicative.) For the Naturals perhaps we want Presburger arithmetic then Additive just contains (+), with `negate` certainly in a different class, perhaps (-) subtract also in a dedicated class. Also there's people wanting Monads with just `bind` not `return`. But restructuring the Prelude classes/methods is just too hard with all that legacy code. Even though you should be able to do:
class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive a) => Num a
Note there's a lot of classes with a single method, and that seems to be an increasing trend. Historically it wasn't so easy in Haskell to do that superclass constraints business; if it had been perhaps there would be more classes with a single method. Then there's some disadvantages to classes holding multiple methods:
* the need to provide an overloading for every method, even though it may not make sense
(or suffer a run-time error, as you say)
* the inability to 'fine tune' methods for a specific datatype [**]
* an internal compiler/object code cost of passing a group of methods in a dictionary as tuple
(as apposed to directly selecting a single method)
[**] Nats vs Integrals vs Fractionals for `Num`; and (this will be controversial, but ...) Some people want to/some languages do use (+) for concatenating Strings/lists. But the other methods in `Num` don't make any sense.
If all your classes have a single method, the class name would seem to be superfluous, and the class/instance decl syntax seems too verbose.
So here's a suggestion. I'll need to illustrate with some definite syntax, but there's nothing necessary about it. (I'll borrow the Explicit Type Application `@`.) To give an instance overloading for method `show` or (==)
show @Int = primShowInt -- in effect pattern matching on the type
(==) @Int = primEqInt -- so see showList below
That is: I'm giving an overloading for those methods on type `Int`. How do I declare those methods are overloadable? In their signature:
show @a :: a -> String -- compare show :: Show a => a -> String
(==) @a :: a -> a -> Bool
Non-overladable functions don't have `@a` to the left of `::`.
How do I show that a class has a superclass constraint? That is: a method has a supermethod constraint, we'll still use `=>`:
show @a :: showsPrec @a => a -> String -- supermethod constraint
show @[a] :: show a => [a] -> String -- instance decl, because not bare a, with constraint =>
show @[a] xss = showList xss
(*) @a :: (+) @a => a -> a -> a
Is this idea completely off the wall? Take a look at Wadler's original 1988 memo introducing what became type classes.
http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fhomepages.inf.ed.ac.uk%2Fwadler%2Fpapers%2Fclass-letter%2Fclass-letter.txt&data=02%7C01%7Csimonpj%40microsoft.com%7C5ec7c3a23a9746bb154b08d62b3a7ba2%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636743927613528630&sdata=vXgR1YLqw8ERzEbhVZBGr%2FpB5fMLMmYtnwt6Bpp4wGs%3D&reserved=0
It reviews several possible designs, but not all those possibilities made it into his paper (with Stephen Blott) later in 1988/January 1989. In particular look at Section 1's 'Simple overloading'. It's what I'm suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler rejects this design because of "potential blow-ups". But he should have pushed the idea a bit further. Perhaps he was scared to allow function/method names into type signatures? (I've already sneaked that in above with constraints.) These days Haskell is getting more relaxed about namespaces: the type `@`pplication exactly allows type names appearing in terms. So to counter his example, the programmer writes:
square x = x * x -- no explicit signature given
square :: (*) @a => a -> a -- signature inferred, because (*) is overloaded
rms = sqrt . square -- no explicit signature
rms :: sqrt @a => a -> a -- signature inferred
Note the inferred signature for `rms` doesn't need `(*) @a` even though it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt` might also have other supermethods, that amount to `Floating`.
... a run-time error results.
Does anyone know of a rationale for this choice, since it seems rather unhaskell-like.
If you allow default method implementations (in the class, as Cale points out), then I guess you have to allow instance decls that don't mention all the methods. I think there should at least be a warning if there's no default method. Also beware the default method might have a more specific signature, which means it can't be applied for some particular instance.
Altogether, I'd say, the culprit is the strong bias in early Haskell to bunch methods together into classes. These days with Haskell's richer/more fine-tuned typeclass features: what do typeclasses do that can't be done more precisely at method level -- indeed that would _better_ be done at method level?
AntC
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fhaskell-prime&data=02%7C01%7Csimonpj%40microsoft.com%7C5ec7c3a23a9746bb154b08d62b3a7ba2%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636743927613528630&sdata=%2FVDtNLEzevef69Qs9rzrd5V2lBJzMLjRAxBBYvbsPAs%3D&reserved=0

Em 2018-10-08 06:21, Anthony Clayden escreveu:
On Mon, 8 Oct 2018 at 8:41 PM, Simon Peyton Jones wrote:
You may be interested in Carlos Camarao’s interesting work. For a long time now he has advocated (in effect) making each function into its own type class, rather that grouping them into classes.
No I think you're mis-apprehending. From the abstract to the group's SBLP2016 paper: "This depends on a modularization of instance visibility, as well as on a redefinition of Haskell’s ambiguity rule."
Hi. I wrote this to mean: "This depends *only* on modularization of instances and a redefinition of Haskell's ambiguity rule" (i.e. no extra mechanism is necessary and all well-typed Haskell programs remain well-typed). Haskell's ambiguity rule is not ok: a type is not ambiguous, it is an expression that is ambiguous, depending on the context where it is used. Global instance scope is not ok either: instances should be modular.
You might remember early last year Carlos submitted a proposal (in two rounds). Your comments were very relevant
https://github.com/ghc-proposals/ghc-proposals/pull/48#issuecomment-28712400...
Relevant because not just was it difficult to understand the proposal, the proposal had no answer to how instance resolution was to behave. "expression ambiguity" turned out to mean: use module scope to resolve overloading.
It is difficut until understanding how simple it really is. The crucial notion of "expression ambiguity" is "overloading resolution" (or: the decision of "overloading is resolved"), based on the existence of "unreachable variables": if and only if there are unreachable variables, satisfiability must be tested for the constraints with unreachable variables. Instance modular scope is secondary.
In the second round of the proposal and in an extended email exchange off-forum with (I think it was) Rodrigo Ribeiro in Carlos' group I tried to tease out how module-scoped instances were going to work for a method exported to a module where there was a different instance in scope. Of course 'orphan instances' are the familiar symptom in GHC.
Wadler & Blott's 1988 paper last paragraph had already explained: "But there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Perhaps that is in line with your thinking.
Not at all. My thinking is coming directly from Wadler's early 1988 memo that I referenced (note *not* the W&B paper) + using some of GHC's more recent features like explicit type application in terms; and its counterpart: explicit method application in types.
Again: the proposal does not need any extra mechanism, just a change to the ambiguity rule and instance modular scope. It would be possible even to maintain instances as global, but in my view this should not be done (it is better to have modular instances).
I wonder how different would have been the history of Haskell if Wadler had not borrowed the terminology "class" and "method". Since Helium has a focus on Haskell learners/beginners: I wonder how much confusion we might have saved those coming from OOP where the terms mean something really quite different. We might have avoided "class" altogether; and talked of "overloaded function".
This is another matter, that does not need to be discussed now: we can avoid type classes, or we can have type classes as optional, but this discussion can be done later. Kind regards, Carlos

On Tue, 9 Oct 2018 at 7:30 AM,
On Mon, 8 Oct 2018 at 8:41 PM, Simon Peyton Jones wrote:
Strange: Simon's message has not appeared on the forum (he did send to it). I've quoted it in full in my reply, but did break it into separate pieces.
Global instance scope is not ok either: instances should be modular.
I just plain disagree. Fundamentally.
Wadler & Blott's 1988 paper last paragraph had already explained: "But there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type. http://foldoc.org/principal We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.) Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions. AntC

Hi.
Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Global instance scope is not ok either: instances should be modular. I just plain disagree. Fundamentally.
Global instance scope is not required for principal typing: a principal type is (just) a type of an expression in a given typing context that has all other types of this expression in that typing context as instances. (Also: instance modularity is not the central issue.) >>> Wadler & Blott's 1988 paper last paragraph had already explained: "But >>> there is no principal type! " >> There is always a principal type, for every expression. >> Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type. http://foldoc.org/principal
A type system has the principal type property if, given a term and a typing context, there exists a type for this term in this typing context such that all other types for this term in this typing context are an instance of this type.
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
A principal type theorem has been proved: see, for example, Theorem 1 in
[1].
Kind regards,
Carlos
[1] Ambiguity and Constrained Polymorphism,
Carlos Camarão, Lucília Figueiredo, Rodrigo Ribeiro,
Science of Computer Programming 124(1), 1--19, August 2016.
On Mon, 8 Oct 2018 at 20:03, Anthony Clayden
On Tue, 9 Oct 2018 at 7:30 AM,
wrote: Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Em 2018-10-08 06:21, Anthony Clayden escreveu:
On Mon, 8 Oct 2018 at 8:41 PM, Simon Peyton Jones wrote:
Strange: Simon's message has not appeared on the forum (he did send to it). I've quoted it in full in my reply, but did break it into separate pieces.
Global instance scope is not ok either: instances should be modular.
I just plain disagree. Fundamentally.
Wadler & Blott's 1988 paper last paragraph had already explained: "But there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type. http://foldoc.org/principal
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

Carlos, local scoping for type classes is flat out not gonna happen in the
haskell language standard any time soon.
if you want to make a case for it, demonstrate its utility, this mailing
list isn't for that. Especially for something that fundamentally changes
the programming model of the language in question in a way that isn't
compatible
merry adventures!
-Carter
On Mon, Oct 8, 2018 at 8:47 PM Carlos Camarao
Hi.
Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Global instance scope is not ok either: instances should be modular. I just plain disagree. Fundamentally.
Global instance scope is not required for principal typing: a principal type is (just) a type of an expression in a given typing context that has all other types of this expression in that typing context as instances.
(Also: instance modularity is not the central issue.)
>>> Wadler & Blott's 1988 paper last paragraph had already explained: "But >>> there is no principal type! "
>> There is always a principal type, for every expression. >> Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type. http://foldoc.org/principal
A type system has the principal type property if, given a term and a typing context, there exists a type for this term in this typing context such that all other types for this term in this typing context are an instance of this type.
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
A principal type theorem has been proved: see, for example, Theorem 1 in [1].
Kind regards,
Carlos
[1] Ambiguity and Constrained Polymorphism, Carlos Camarão, Lucília Figueiredo, Rodrigo Ribeiro, Science of Computer Programming 124(1), 1--19, August 2016.
On Mon, 8 Oct 2018 at 20:03, Anthony Clayden
wrote: On Tue, 9 Oct 2018 at 7:30 AM,
wrote: Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Em 2018-10-08 06:21, Anthony Clayden escreveu:
On Mon, 8 Oct 2018 at 8:41 PM, Simon Peyton Jones wrote:
Strange: Simon's message has not appeared on the forum (he did send to it). I've quoted it in full in my reply, but did break it into separate pieces.
Global instance scope is not ok either: instances should be modular.
I just plain disagree. Fundamentally.
Wadler & Blott's 1988 paper last paragraph had already explained: "But there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type. http://foldoc.org/principal
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

Hi Carter, I am not proposing "local scoping". I think local scoping does not have substantial gains and at least introduces some difficulties and complexity (I have tried it in system CT). Even modular scope for instances is not mandatory, as I said. A general defaulting rule is a remedy, if instance modular scope is not supported, for changing the ambiguity rule (I prefer modular instance scoping though). I don't want to fight for anything. I'd like to contribute if the Haskell community friendly wishes me to do so in order to introduce MPTCs in a relatively simple way, without the need of extra mechanisms, based essentially on changing the ambiguity rule: I think a type like, say, (F a b, X a) => b is not ambiguous (F and X being classes with members f:: a->b and x::a, say), since then overloading of (f x) can be resolved, with a new ambiguity rule, depending on the context (or type) where (f x) is used. Kind regards, Carlos Em 2018-10-10 12:52, Carter Schonwald escreveu:
Carlos, local scoping for type classes is flat out not gonna happen in the haskell language standard any time soon.
if you want to make a case for it, demonstrate its utility, this mailing list isn't for that. Especially for something that fundamentally changes the programming model of the language in question in a way that isn't compatible
merry adventures! -Carter
On Mon, Oct 8, 2018 at 8:47 PM Carlos Camarao
wrote: Hi.
Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Global instance scope is not ok either: instances should be modular. I just plain disagree. Fundamentally.
Global instance scope is not required for principal typing: a principal type is (just) a type of an expression in a given typing context that has all other types of this expression in that typing context as instances.
(Also: instance modularity is not the central issue.)
Wadler & Blott's 1988 paper last paragraph had already explained: "But there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type. http://foldoc.org/principal
A type system has the principal type property if, given a term and a typing context, there exists a type for this term in this typing context such that all other types for this term in this typing context are an instance of this type.
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
A principal type theorem has been proved: see, for example, Theorem 1 in [1].
Kind regards,
Carlos
[1] Ambiguity and Constrained Polymorphism, Carlos Camarão, Lucília Figueiredo, Rodrigo Ribeiro, Science of Computer Programming 124(1), 1--19, August 2016.
On Mon, 8 Oct 2018 at 20:03, Anthony Clayden
wrote: On Tue, 9 Oct 2018 at 7:30 AM,
wrote: Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Em 2018-10-08 06:21, Anthony Clayden escreveu:
On Mon, 8 Oct 2018 at 8:41 PM, Simon Peyton Jones wrote:
Strange: Simon's message has not appeared on the forum (he did send to it). I've quoted it in full in my reply, but did break it into separate pieces.
Global instance scope is not ok either: instances should be modular.
I just plain disagree. Fundamentally.
Wadler & Blott's 1988 paper last paragraph had already explained:
"But
there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type.
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

ok, cool! I'm not sure what modular scoping would look like, but it'd be
fun what that looks like!
I do think that the prime list isn't the best list though for figuring that
out / experimentations thereof :)
On Wed, Oct 10, 2018 at 1:36 PM
Hi Carter,
I am not proposing "local scoping". I think local scoping does not have substantial gains and at least introduces some difficulties and complexity (I have tried it in system CT).
Even modular scope for instances is not mandatory, as I said. A general defaulting rule is a remedy, if instance modular scope is not supported, for changing the ambiguity rule (I prefer modular instance scoping though).
I don't want to fight for anything. I'd like to contribute if the Haskell community friendly wishes me to do so in order to introduce MPTCs in a relatively simple way, without the need of extra mechanisms, based essentially on changing the ambiguity rule: I think a type like, say, (F a b, X a) => b is not ambiguous (F and X being classes with members f:: a->b and x::a, say), since then overloading of (f x) can be resolved, with a new ambiguity rule, depending on the context (or type) where (f x) is used.
Kind regards,
Carlos
Em 2018-10-10 12:52, Carter Schonwald escreveu:
Carlos, local scoping for type classes is flat out not gonna happen in the haskell language standard any time soon.
if you want to make a case for it, demonstrate its utility, this mailing list isn't for that. Especially for something that fundamentally changes the programming model of the language in question in a way that isn't compatible
merry adventures! -Carter
On Mon, Oct 8, 2018 at 8:47 PM Carlos Camarao
wrote: Hi.
Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Global instance scope is not ok either: instances should be modular. I just plain disagree. Fundamentally.
Global instance scope is not required for principal typing: a principal type is (just) a type of an expression in a given typing context that has all other types of this expression in that typing context as instances.
(Also: instance modularity is not the central issue.)
Wadler & Blott's 1988 paper last paragraph had already explained: "But there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type. http://foldoc.org/principal
A type system has the principal type property if, given a term and a typing context, there exists a type for this term in this typing context such that all other types for this term in this typing context are an instance of this type.
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
A principal type theorem has been proved: see, for example, Theorem 1 in [1].
Kind regards,
Carlos
[1] Ambiguity and Constrained Polymorphism, Carlos Camarão, Lucília Figueiredo, Rodrigo Ribeiro, Science of Computer Programming 124(1), 1--19, August 2016.
On Mon, 8 Oct 2018 at 20:03, Anthony Clayden
wrote: On Tue, 9 Oct 2018 at 7:30 AM,
wrote: Thanks Carlos. I wish I could say thank you for clarifying, but I'm afraid this is as muddled as all the comments on the two proposals.
I don't want to go over it again. I just want to say that my suggestion earlier in the thread is fundamentally different.
Em 2018-10-08 06:21, Anthony Clayden escreveu:
On Mon, 8 Oct 2018 at 8:41 PM, Simon Peyton Jones wrote:
Strange: Simon's message has not appeared on the forum (he did send to it). I've quoted it in full in my reply, but did break it into separate pieces.
Global instance scope is not ok either: instances should be modular.
I just plain disagree. Fundamentally.
Wadler & Blott's 1988 paper last paragraph had already explained:
"But
there is no principal type! "
There is always a principal type, for every expression. Of course the type depends on the context where the expression occurs.
Then it's not a _principal_ type for the expression, it's just a local type.
We arrive at the principal type by unifying the principal types of the sub-expressions, down to the principal types of each atom. W&B are pointing out that without global scope for instances, typing cannot assign a principal type to each method. (They left that as an open problem at the end of the paper. Haskell has resolved that problem by making all instances global. Changing Haskell to modular instances would be a breakage. Fundamentally.)
Under my suggestion, we can assign a (global) principal type to each method -- indeed you must, by giving a signature very similar to a class declaration; and that distinguishes overloaded functions from parametric polymorphic functions.
AntC _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

Am 08.10.2018 um 11:21 schrieb Anthony Clayden:
I wonder how different would have been the history of Haskell if Wadler had not borrowed the terminology "class" and "method". Since Helium has a focus on Haskell learners/beginners: I wonder how much confusion we might have saved those coming from OOP where the terms mean something really quite different. We might have avoided "class" altogether; and talked of "overloaded function".
Similar to C++, perhaps? Cheers Ben

Am 06.10.2018 um 05:18 schrieb Anthony Clayden:
On Sat, 6 Oct 2018 at 9:47 AM, Petr Pudlák
wrote: such as the important laws between `return` and `>>=`. And then for example a class with just `return` doesn't give any information what `return x` means or what should be its properties.
Then make Bind a superclass constraint on `return` (or vice versa, or both ways).
Just as the laws for Num's methods are defined in terms of equality
x + negate x == fromInteger 0 -- for example
Talking about laws is a red herring: you can't declare the laws/the compiler doesn't enforce them or rely on them in any way. Indeed the Lensaholics seem to take pleasure in building lenses that break the (van Laarhoven) laws.
I strongly disagree with this. Class laws are absolutely essential. They are the main distinguishing feature of Haskell classes versus the usual ad-hoc overloading found in most mainstream (e.g. OO) languages. Using '+' for string concatenation? That's just a poor work-around for languages that only support a fixed set of traditional operators. And if you have a Monoid or Semigroup class that doesn't require or even suggest commutativity of the operator, but clearly states that associativity is required, then I see absolutely no reason to use '+' for that. That the compiler can't enforce the laws is irrelevant. Laws are a contract and violating it is a bug. Non law-abiding lenses like 'filtered' are clearly documented with severe warnings attached. To cite them as proof that people take pleasure in violating class laws is ridiculous. Granted, classes that combine multiple methods are not /required/ to state laws. But they offer a convenient place where to put them.
For example, in Haskell we could have
class (Return m, Bind m) => Monad m where
without any methods specified. But instances of `Monad` should be only such types for which `return` and `>>=` satisfy the monad laws.
First: what does "satisfy the xxx laws" mean? The Haskell report and GHC's Prelude documentation state a bunch of laws; and it's a good discipline to write down laws if you're creating a class; but it's only documentation.
Why you say "only"? Documentation is essential and documentation in the form of laws (properties) is the most useful sort of documentation. And many class laws (though not all) /can/ be formally expressed as Haskell code and thus tested with e.g. quickcheck.
Arguably IO, the most commonly used Monad, breaks the Monad laws in rather serious ways because it imposes sequence of execution;
I think such a bold statement should be accompanied by an example that demonstrates it. Cheers Ben
participants (9)
-
Anthony Clayden
-
Ben Franksen
-
camarao@dcc.ufmg.br
-
Carlos Camarao
-
Carter Schonwald
-
Jurriaan Hage
-
Petr Pudlák
-
Philippa Cowderoy
-
Simon Peyton Jones