Show, Eq not necessary for Num [Was: Revamping the numeric classes]

{I'm diverting this discussion to haskell-cafe.} [I am not sure a more mathematically correct numeric class system is suitable for inclusion in the language specification of Haskell (a library would certainly be useful though). But this is not my topic in this letter.] On Wed, 7 Feb 2001, Brian Boutel wrote:
* Haskell equality is a defined operation, not a primitive, and may not be decidable. It does not always define equivalence classes, because a==a may be Bottom, so what's the problem? It would be a problem, though, to have to explain to a beginner why they can't print the result of a computation.
The fact that equality can be trivially defined as bottom does not imply that it should be a superclass of Num, it only explains that there is an ugly way of working around the problem. Neither is the argument that the beginner should be able to print the result of a computation a good argument for having Show as a superclass. A Num class without Eq, Show as superclasses would only mean that the implementor is not _forced_ to implement Eq and Show for all Num instances. Certainly most instances of Num will still be in both Show and Eq, so that they can be printed and shown, and one can easily make sure that all Num instances a beginner encounters would be such. As far as I remember from the earlier discussion, the only really visible reason for Show, Eq to be superclasses of Num is that class contexts are simpler when (as is often the case) numeric operations, equality and show are used in some context. f :: Num a => a -> String -- currently f a = show (a+a==2*a) If Show, Eq, Num were uncoupled this would be f :: (Show a, Eq a, Num a) => a -> String But I think I could live with that. (In fact, I rather like it.) Another unfortunate result of having Show, Eq as superclasses to Num is that for those cases when "trivial" instances (of Eq and Show) are defined just to satisfy the current class systems, the users have no way of supplying their own instances. Due to the Haskell rules of always exporting instances we have that if the Num instance is visible, so are the useless Eq and Show instances. In the uncoupled case the users have the choice to define Eq and Show instances that make sense to them. A library designer could provide the Eq and Show instances in two separate modules to give the users maximum flexibility. /Patrik Jansson

Patrik Jansson wrote:
[I am not sure a more mathematically correct numeric class system is suitable for inclusion in the language specification of Haskell (a library would certainly be useful though)....]
I think it should be done at the language level. Previously Brian Boutel wrote: ...
Haskell was intended for use by programmers who may not be mathematicians, as a general purpose language. Changes to make keep mathematicians happy tend to make it less understandable and attractive to everyone else.
Specifically:
* most usage of (+), (-), (*) is on numbers which support all of them.
* Haskell equality is a defined operation, not a primitive, and may not be decidable. It does not always define equivalence classes, because a==a may be Bottom, so what's the problem? It would be a problem, though, to have to explain to a beginner why they can't print the result of a computation.
==== Some people here might recall that I cried loudly and in despair (OK, I am exaggerating a bit...) about the inadequacy of the Num hierarchy much before Sergey Mechveliani's proposal. Finally I implemented my own home-brewed hierarchy of Rings, AdditiveGroups, Modules, etc. in order to play with differential structures and graphical objects. And arithmetic on functions. I AM NOT A MATHEMATICIAN, and still, I see very strongly the need for a sane math layer in Haskell on behalf of 'general purpose' programming. Trying to explain to comp. sci students (who, at least here, don't like formal mathematics too much...) WHY the Haskell Num hierarchy is as it is, is simply hopeless, because some historical accidents were never very rational. * I don't care about "most usage of (+), (-), (*) is on numbers which support all of them" if this produces a chaos if you want to use Haskell for geometry, or graphics, needing vectors.
From this point of view a slightly simpler (in this context) type system of Clean seems to be better. And I appreciate also the possibility to define arithmetic operations on *functions*, which is impossible in Haskell because of this Eq/Show superclass constraints.
In the uncoupled case the users have the choice to define Eq and Show instances that make sense to them. A library designer could provide the Eq and Show instances in two separate modules to give the users maximum flexibility.
/Patrik Jansson
Yes. I don't want to be too acrimonious nor sarcastic, but those people who claim that Haskell as a "universal" language should not follow too closely a decent mathematical discipline, serve the devil. When math is taught at school at the elementary level, with full knowledge of the fact that almost nobody will follow the mathematical career afterwards, the rational, logical side of all constructions is methodologically essential. 10 years old pupils learn that you can add two dollars to 7 dollars, but multiplying dollars has not too much sense (a priori), and adding dollars to watermelons is dubious. Numbers are delicate abstractions, and treating them in a cavalière manner in a supposedly "universal" language, harms not only mathematicians. As you see, treating (*) together with (+) is silly not only to vector spaces, but also for dimensional quantities, useful outside math (if only for debugging). "Ch. A. Herrmann" wrote:
the problem is that the --majority, I suppose?-- of mathematicians tend to overload operators. They use "*" for matrix-matrix multiplication as well as for matrix-vector multiplication etc.
Therefore, a quick solution that implements groups, monoids, Abelian groups, rings, Euclidean rings, fields, etc. will not be sufficient.
I don't think that it is acceptable for a language like Haskell to permit the user to overload predefined operators, like "*".
Wha do you mean "predefined" operators? Predefined where? Forbid what? Using the standard notation even to multiply rationals or complexes? And leave this possibility open to C++ programmers who can overload anything without respecting mathematical congruity? Why? A serious mathematician who sees the signature (*) :: a -> a -> a won't try to use it for multiplying a matrix by a vector. But using it as a basic operator within a monoid is perfectly respectable. No need to "lift" or "promote" scalars into vectors/matrices, etc. For "scaling" I use personally an operation (*>) defined within the Module constructor class, but I am unhappy, because (*>) :: a -> (t a) -> (t a) declared in a Module instance of the constructor t prevents from using it in the case where (t a) in reality is a. (By default (*>) maps (x*) through the elements of (t ...), and kinds "*" are not constructors... Jerzy Karczmarczuk Caen, France

Hi Haskellers,
"Jerzy" == Jerzy Karczmarczuk
writes: Jerzy> "Ch. A. Herrmann" wrote:
>> the problem is that the --majority, I suppose?-- of >> mathematicians tend to overload operators. They use "*" for >> matrix-matrix multiplication as well as for matrix-vector >> multiplication etc. >> >> Therefore, a quick solution that implements groups, monoids, >> Abelian groups, rings, Euclidean rings, fields, etc. will not be >> sufficient. >> >> I don't think that it is acceptable for a language like Haskell >> to permit the user to overload predefined operators, like "*". Jerzy> Wha do you mean "predefined" operators? Predefined where? In hugs, ":t (*)" tells you: (*) :: Num a => a -> a -> a which is an intended property of Haskell, I suppose. Jerzy> Forbid what? A definition like (a trivial example, instead of matrix/vector) class NewClass a where (*) :: a->[a]->a leads to an error since (*) is already defined on top level, e.g. Repeated definition for member function "*" in hugs, although I didn't specify that I wanted to use (*) in the context of the Num class. However, such things work in local definitions: Prelude> let (*) a b = a++(show b) in "Number " * 5 "Number 5" but you certainly don't want it to use (*) only locally. Jerzy> Using the standard notation even to multiply Jerzy> rationals or complexes? No, that's OK since they belong to the Num class. But as soon as you want to multiply a rational with a complex you'll get a type error. Personally, I've nothing against this strong typing discipline, since it'll catch some errors. Jerzy> And leave this possibility open to C++ programmers who can Jerzy> overload anything without respecting mathematical congruity? Jerzy> Why? If mathematics is to be respected, we really have to discuss a lot of things, e.g., whether it is legal to define comparison for floating point numbers, but that won't help much. Also, the programming language should not prescribe that the "standard" mathematics is the right mathematics and the only the user is allowed to deal with. If the user likes to multiply two strings, like "ten" * "six" (= "sixty"), and he/she has a semantics for that, why not? Jerzy> A serious mathematician who sees the signature Jerzy> (*) :: a -> a -> a Jerzy> won't try to use it for multiplying a matrix by a Jerzy> vector. A good thing would be to allow the signature (*) :: a -> b -> c as well as multi-parameter type classes (a, b and c) and static overloading, as Joe Waldmann suggested. Jerzy> No need to "lift" or "promote" Jerzy> scalars into vectors/matrices, etc. You're right, there is no "need". We can live with a :*: b for matrix multiplication, and with a <*> b for matrix/vector multiplication, etc. It's a matter of style. If anyone has experiences with defining operators in unicode and editing them without problems, please tell me. Unicode will provide enough characters for a distinction, I suppose. Bye -- Christoph Herrmann E-mail: herrmann@fmi.uni-passau.de WWW: http://brahms.fmi.uni-passau.de/cl/staff/herrmann.html

"Ch. A. Herrmann" answers my questions:
Jerzy> What do you mean "predefined" operators? Predefined where?
In hugs, ":t (*)" tells you: (*) :: Num a => a -> a -> a which is an intended property of Haskell, I suppose.
Aha. But I would never call this a DEFINITION of this operator. This is just the type, isn't it? A misunderstanding, I presume.
Jerzy> Forbid what? A definition like (a trivial example, instead of matrix/vector) class NewClass a where (*) :: a->[a]->a leads to an error
OK, OK. Actually my only point was to suggest that the type for (*) as above should be constrained oinly by an *appropriate class*, not by this horrible Num which contains additive operators as well. So this is not the answer I expected, concerning the "overloading of a predefined operator". BTW. In Clean (*) constitutes a class by itself, that is this simplicity I appreciate, although I am far from saying that they have an ideal type system for a working mathemaniac.
... Also, the programming language should not prescribe that the "standard" mathematics is the right mathematics and the only the user is allowed to deal with. If the user likes to multiply two strings, like "ten" * "six" (= "sixty"), and he/she has a semantics for that, why not?
Aaa, here we might, although need not disagree. I would like to see some rational constraints, preventing the user from inventing a completely insane semantics for this multiplication, mainly to discourage writing of programs impossible to understand. Jerzy Karczmarczuk Caen, France

On 07-Feb-2001 Patrik Jansson wrote: (interesting stuff deleted)
As far as I remember from the earlier discussion, the only really visible reason for Show, Eq to be superclasses of Num is that class contexts are simpler when (as is often the case) numeric operations, equality and show are used in some context.
f :: Num a => a -> String -- currently f a = show (a+a==2*a)
If Show, Eq, Num were uncoupled this would be
f :: (Show a, Eq a, Num a) => a -> String
But I think I could live with that. (In fact, I rather like it.)
Basically I'm too. However, what is missing for me is something like: type Comfortable a = (Show a, Eq a, Num a) => a or class (Show a, Read a, Eq a) => Comfortable a instance (Show a, Read a, Eq a) => Comfortable a I think here is a point where a general flaw of class hierachies as a mean of software design becomes obvious, which consists of forcing the programmer to arbitrarily prefer few generalizations to all others in a global, context-independent design decision. The oo community (being the source of all the evil...) usually relies on the rather problematic ontological assumption that, at least from a certain point of view (problem domain, design, implemention), the relevant concepts form in a natural way a kind a generalization hierarchy, and that this generalization provides a natural way to design the software (in our case, determine the type system in some a-priory fashion). Considering the fact that a concept, for which (given a certain point of view) n elementary predicates hold a-priory, n! possible generalizations exist a-priory, this assumption can be questioned. In contrary to the given assumption, I have made the experience that, when trying to classify concepts, even a light shift in the situation being under consideration can lead to a severe change in what appears to be the "natural" classification. Besides this, as is apparent in Show a => Num a, it is not always a priory generalizations that are really needed. Instead, the things must be fit into the current point of view with a bit force, thus changing concepts or even inventing new ones. (For example, in the oo community, which likes (or is forced?) to "ontologize" relationships into "objects", has invented "factories" for different things, ranging from GUI border frames to database connection handles. Behind such an at first glance totally arbitary conceptualization might stand a more rational concept, for example applying a certain library design principle called "factory" to different types of things. However one can't always wait until the rationale behind a certain solution is clearly recognized.) In my experience, both class membership and generalization relationships are often needed locally and post hoc, and they sometimes even express empirical (a-posteriory) relations between concepts instead of true analytical (a-priory) generalization relationships. As a consequence, for my opinion, programming languages should make it possible and easy to employ post-hoc and local class membership declarations and post-hoc and local class hierarchy declarations (or even re-organizations). There will of course be situations where a global a-priory declaration of generalization nevertheless still make completely sense. For Haskell, I could imagine (without having having much thought about) in addition to the things mentioned in the beginning, several things making supporting the "locally, fast and easy", including a mean to define classes with implied memberships, for example declarations saying that "Foo is the class of all types in scope for which somefoo :: ... is defined", or declarations saying that "class Num is locally restricted to all instances of global Num which also belong to Eq". Elke. --- Elke Kasimir Skalitzer Str. 79 10997 Berlin (Germany) fon: +49 (030) 612 852 16 mail: elke.kasimir@catmint.de> see: http://www.catmint.de/elke for pgp public key see: http://www.catmint.de/elke/pgp_signature.html

Thu, 08 Feb 2001 15:11:21 +0100 (CET), Elke Kasimir
However, what is missing for me is something like:
type Comfortable a = (Show a, Eq a, Num a) => a
or
class (Show a, Read a, Eq a) => Comfortable a instance (Show a, Read a, Eq a) => Comfortable a
I agree and think it should be easy to add. The latter syntax is nice: obvious what it means, not legal today. This instance of course conflicts with any other instance of that class, so it can be recognized and treated specially as a "class synonym".
For Haskell, I could imagine (without having having much thought about) in addition to the things mentioned in the beginning, several things making supporting the "locally, fast and easy", including a mean to define classes with implied memberships, for example declarations saying that "Foo is the class of all types in scope for which somefoo :: ... is defined", or declarations saying that "class Num is locally restricted to all instances of global Num which also belong to Eq".
Here I would be more careful. Don't know if local instances or local classes can be defined to make sense, nor if they could be useful enough... -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

Patrik Jansson wrote:
On Wed, 7 Feb 2001, Brian Boutel wrote:
* Haskell equality is a defined operation, not a primitive, and may not be decidable. It does not always define equivalence classes, because a==a may be Bottom, so what's the problem? It would be a problem, though, to have to explain to a beginner why they can't print the result of a computation.
The fact that equality can be trivially defined as bottom does not imply that it should be a superclass of Num, it only explains that there is an ugly way of working around the problem. Neither is the argument that the beginner should be able to print the result of a computation a good argument for having Show as a superclass.
There is nothing trivial or ugly about a definition that reflects reality and bottoms only where equality is undefined. Of course, if you do not need to apply equality to your "numeric" type then having to define it is a waste of time, but consider this: - Having a class hierarchy at all (or making any design decision) implies compromise. - The current hierarchy (and its predecessors) represent a reasonable compromise that meets most needs. - Users have a choice: either work within the class hierarchy and accept the pain of having to define things you don't need in order to get the things that come for free, or omit the instance declarations and work outside the hierarchy. In that case you will not be able to use the overloaded operator symbols of the class, but that is just a matter of concrete syntax, and ultimately unimportant. --brian

On Thu, Feb 08, 2001 at 08:51:57PM +0000, Marcin 'Qrczak' Kowalczyk wrote:
... class (Show a, Read a, Eq a) => Comfortable a instance (Show a, Read a, Eq a) => Comfortable a ... The latter syntax is nice: obvious what it means, not legal today. This instance of course conflicts with any other instance of that class, so it can be recognized and treated specially as a "class synonym".
Why isn't it legal? I just tried it, and Hugs accepted it, with or without extensions. "where" clauses are optional, right?
.... Don't know if local instances or local classes can be defined to make sense, nor if they could be useful enough...
Well, let's see. Local classes already exist: just don't export them. Local instances would not be hard to add with special syntax, though really they should be part of a more general mechanism for dealing with instances explicitly. Agreed that they might not be useful enough. Best, Dylan Thurston

Fri, 9 Feb 2001 11:48:33 -0500, Dylan Thurston
class (Show a, Read a, Eq a) => Comfortable a instance (Show a, Read a, Eq a) => Comfortable a
Why isn't it legal?
Because in Haskell 98 instance's head must be of the form of a type constructor applied to type variables. Here it's a type variable.
I just tried it, and Hugs accepted it, with or without extensions.
My Hugs does not accept it without extensions. ghc does not accept it by default. ghc -fglasgow-exts accepts an instance's head which is a type constructor applied to some other types than just type variables (e.g. instance Foo [Char]), and -fallow-undecidable-instances lets it accept the above too. I forgot that it can make context reduction infinite unless the compiler does extra checking to prevent this. I guess that making it legal keeps the type system decidable, only compilers would have to introduce some extra checks. Try the following module: ------------------------------------------------------------------------ module Test where class Foo a where foo :: a class Bar a where bar :: a class Baz a where baz :: a instance Foo a => Bar a where bar = foo instance Bar a => Baz a where baz = bar instance Baz a => Foo a where foo = baz f = foo ------------------------------------------------------------------------ Both hugs -98 and ghc -fglasgow-exts -fallow-undecidable-instances reach their limits of context reduction steps. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

On 09-Feb-2001, Brian Boutel
Patrik Jansson wrote:
The fact that equality can be trivially defined as bottom does not imply that it should be a superclass of Num, it only explains that there is an ugly way of working around the problem.
...
There is nothing trivial or ugly about a definition that reflects reality and bottoms only where equality is undefined.
I disagree. Haskell is a statically typed language, and having errors
which could easily be detected at compile instead being deferred to
run time is ugly in a statically typed language.
--
Fergus Henderson

Fergus Henderson wrote:
On 09-Feb-2001, Brian Boutel
wrote: Patrik Jansson wrote:
The fact that equality can be trivially defined as bottom does not imply that it should be a superclass of Num, it only explains that there is an ugly way of working around the problem.
...
There is nothing trivial or ugly about a definition that reflects reality and bottoms only where equality is undefined.
I disagree. Haskell is a statically typed language, and having errors which could easily be detected at compile instead being deferred to run time is ugly in a statically typed language.
There may be some misunderstanding here. If you are talking about type for which equality is always undefined, then I agree with you, but that is not what I was talking about. I was thinking about types where equality is defined for some pairs of argument values and undefined for others - I think the original example was some kind of arbitrary precision reals. My remark about "a definition that reflects reality and bottoms only where equality is undefined" was referring to this situation. Returning to the basic issue, I understood the desire to remove Eq as a superclass of Num was so that people were not required to implement equality if they did not need it, not that there were significant numbers of useful numeric types for which equality was not meaningful. Whichever of these was meant, I feel strongly that accomodating this and other similar changes by weakening the constraints on what Num in Haskell implies, is going too far. It devalues the Class structure in Haskell to the point where its purpose, to control ad hoc polymorphism in a way that ensures that operators are overloaded only on closely related types, is lost, and one might as well abandon Classes and allow arbitrary overloading. --brian --brian

On 11-Feb-2001, Brian Boutel
Fergus Henderson wrote:
On 09-Feb-2001, Brian Boutel
wrote: Patrik Jansson wrote:
The fact that equality can be trivially defined as bottom does not imply that it should be a superclass of Num, it only explains that there is an ugly way of working around the problem.
...
There is nothing trivial or ugly about a definition that reflects reality and bottoms only where equality is undefined.
I disagree. Haskell is a statically typed language, and having errors which could easily be detected at compile instead being deferred to run time is ugly in a statically typed language.
There may be some misunderstanding here. If you are talking about type for which equality is always undefined, then I agree with you, but that is not what I was talking about. I was thinking about types where equality is defined for some pairs of argument values and undefined for others - I think the original example was some kind of arbitrary precision reals.
The original example was treating functions as a numeric type. In the case of functions, computing equality is almost always infeasible. But you can easily define addition etc. pointwise: f + g = (\ x -> f x + g x)
Returning to the basic issue, I understood the desire to remove Eq as a superclass of Num was so that people were not required to implement equality if they did not need it, not that there were significant numbers of useful numeric types for which equality was not meaningful.
The argument is the latter, with functions as the canonical example.
--
Fergus Henderson

On 11-Feb-2001, Brian Boutel
There may be some misunderstanding here. If you are talking about type for which equality is always undefined, then I agree with you, but that is not what I was talking about. I was thinking about types where equality is defined for some pairs of argument values and undefined for others - I think the original example was some kind of arbitrary precision reals.
On Sun, Feb 11, 2001 at 06:24:33PM +1100, Fergus Henderson wrote:
The original example was treating functions as a numeric type. In the case of functions, computing equality is almost always infeasible. But you can easily define addition etc. pointwise:
f + g = (\ x -> f x + g x)
I have a fairly complete implementation of this with dummy instances of
Eq and Show for those who want to see the consequences of this. I found,
interestingly enough, that any type constructor f with the following
three properties could have an instance of Num defined upon f a:
(1) it has a unary constructor to lift scalars
(2) it has a Functor instance
(3) it has an analogue of zip which can be defined upon it
or, more precisely:
\begin{code}
instance (Eq (f a), Show (f a), Num a, Functor f,
Zippable f, HasUnaryCon f) => Num (f a)
where
f + g = fmap (uncurry (+)) $ fzip f g
f * g = fmap (uncurry (*)) $ fzip f g
f - g = fmap (uncurry (-)) $ fzip f g
negate = fmap negate
abs = fmap abs
signum = fmap signum
fromInteger = unaryCon . fromInteger
class Zippable f where
fzip :: f a -> f b -> f (a,b)
class HasUnaryCon f where
unaryCon :: a -> f a
instance Functor ((->) a) where
fmap = (.)
instance Zippable ((->) a) where
fzip f g = \x -> (f x, g x)
instance HasUnaryCon ((->) a) where
unaryCon = const
\end{code}
and this generalizes nicely to other data types:
\begin{code}
instance Zippable Maybe where
fzip (Just x) (Just y) = Just (x,y)
fzip _ Nothing = Nothing
fzip Nothing _ = Nothing
instance HasUnaryCon Maybe where
unaryCon = Just
instance Zippable [ ] where
fzip = zip
instance HasUnaryCon [ ] where
unaryCon = cycle . (:[])
\end{code}
On 11-Feb-2001, Brian Boutel
Returning to the basic issue, I understood the desire to remove Eq as a superclass of Num was so that people were not required to implement equality if they did not need it, not that there were significant numbers of useful numeric types for which equality was not meaningful.
On Sun, Feb 11, 2001 at 06:24:33PM +1100, Fergus Henderson wrote:
The argument is the latter, with functions as the canonical example.
Well, usually equality as a mathematical concept is meaningful, but either not effectively or efficiently computable. Given an enumerable and bounded domain, equality may be defined (perhaps inefficiently) on functions by \begin{code} instance (Enum a, Bounded a, Eq b) => Eq (a->b) where f == g = all (uncurry (==)) $ zipWith (\x -> (f x, g x)) [minBound..maxBound] \end{code} and as I've said in another post, equality instances on data structures expected to be infinite, very large, or where the semantics of equality are make it difficult to compute, or perhaps even cases where it's just not useful are also not good to be forced. Cheers, Bill
participants (9)
-
Brian Boutel
-
Ch. A. Herrmann
-
Dylan Thurston
-
Elke Kasimir
-
Fergus Henderson
-
Jerzy Karczmarczuk
-
Patrik Jansson
-
qrczak@knm.org.pl
-
William Lee Irwin III