Justification for Ord inheriting from Eq?

Hi - I've been wondering for a long time if there is a reason why Ord should inherit from Eq and not vice versa, or whether in fact there is any justification for making either Ord or Eq inherit from the other one. For example, Ord and Eq could alternatively be defined as: class Ord a where (<), (<=), (>=), (>) : a -> a -> Bool x <= y = not (y < x) x >= y = not (x < y) x > y = y < x class Ord a => Eq a where (==), (/=) :: a -> a -> Bool x /= y = x < y || y < x x == y = not (x /= y) Part of the reason for my question is that it seems to me that the lesson from object oriented programming is that inheritance is usually a bad idea, since very few things (perhaps nothing?) have a single natural taxonomy (witness the efforts to reorganise the numeric hierarchy that have been alluded to on this list). In languages such as C++ the only "good" use of inheritance seems to be when you have an abstract base class representing an interface and multiple concrete derived classes (as immediate children of it) representing the implementations, but in Haskell, this is the class/instance distinction, so I can't see a strong reason why Haskell classes should be allowed to inherit from other classes. Except perhaps Monad, MonadIO, MonadPlus etc... Any thoughts? Thanks, Brian.

On Thu, Apr 06, 2006 at 09:31:24PM +0100, Brian Hulley wrote:
I've been wondering for a long time if there is a reason why Ord should inherit from Eq and not vice versa, or whether in fact there is any justification for making either Ord or Eq inherit from the other one.
The problem is that having an order implies you have equality, so deriving Eq from Ord won't actually mean anything. a == b = a <= b && b <= a that and there are many things that have an equivalance relationship on them, but no total ordering. as to why there isn't a partial ordering class between Eq and Ord, that is a good question. in haskell classes _do_ define interfaces, not concrete representations so the problems with inherentence of non-abstract classes in OO languages don't apply. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham wrote:
On Thu, Apr 06, 2006 at 09:31:24PM +0100, Brian Hulley wrote:
I've been wondering for a long time if there is a reason why Ord should inherit from Eq and not vice versa, or whether in fact there is any justification for making either Ord or Eq inherit from the other one.
The problem is that having an order implies you have equality, so deriving Eq from Ord won't actually mean anything.
Thanks, I didn't think of it that way.
in haskell classes _do_ define interfaces, not concrete representations so the problems with inherentence of non-abstract classes in OO languages don't apply.
What I was trying to argue was that inheritance of classes in Haskell is not needed because the only "good" use (IMO) of inheritance in other languages is already dealt with in Haskell by the class/instance distinction: the classes defining the interfaces and the instances defining the concrete implementations. The problem of allowing classes (in Haskell) to inherit is that you end up with heirarchies which fix the design according to some criteria which may later turn out to be invalid, whereas if there were no hierarchies then you could just use the particular classes that are needed for the particular function, eg explicitly supplying Eq and Ord instead of just Ord etc (though for a sort function Ord by itself would be sufficient). For example the re-organisation of numeric classes might not have been necessary if there were no inheritance relationships between them (though I don't know enough details to take this example further). Regards, Brian.

On Thu, Apr 06, 2006 at 10:52:52PM +0100, Brian Hulley wrote:
in haskell classes _do_ define interfaces, not concrete representations so the problems with inherentence of non-abstract classes in OO languages don't apply.
What I was trying to argue was that inheritance of classes in Haskell is not needed because the only "good" use (IMO) of inheritance in other languages is already dealt with in Haskell by the class/instance distinction: the classes defining the interfaces and the instances defining the concrete implementations.
The problem of allowing classes (in Haskell) to inherit is that you end up with heirarchies which fix the design according to some criteria which may later turn out to be invalid, whereas if there were no hierarchies then you could just use the particular classes that are needed for the particular function, eg explicitly supplying Eq and Ord instead of just Ord etc (though for a sort function Ord by itself would be sufficient).
For example the re-organisation of numeric classes might not have been necessary if there were no inheritance relationships between them (though I don't know enough details to take this example further).
well, there are a few reasons you would want to use inheritance in haskell, some good, some bad. 1. one really does logically derive from the other, Eq and Ord are like this, the rules of Eq says it must be an equivalance relation and that Ord defines a total order over that equivalance relation. this is a good thing, as it lets you write code that depends on these properties. 2. it is more efficient on dictionary passing implementations of typeclasses. (does not apply to typecase based implementations like jhc) 3. it is simpler to declare instances for, the default methods of Ord can depend on Eq. 1 is a very good reason. 2 not so much, but not irrelevant. 3 should not be a very good reason at all. the inflexability of the class hierarchy was my motivation for the class aliases proposal. http://repetae.net/john/recent/out/classalias.html John -- John Meacham - ⑆repetae.net⑆john⑈

On Thursday 06 April 2006 06:44 pm, John Meacham wrote:
On Thu, Apr 06, 2006 at 10:52:52PM +0100, Brian Hulley wrote:
[snip a question about Eq and Ord classes]
well, there are a few reasons you would want to use inheritance in haskell, some good, some bad.
1. one really does logically derive from the other, Eq and Ord are like this, the rules of Eq says it must be an equivalance relation and that Ord defines a total order over that equivalance relation. this is a good thing, as it lets you write code that depends on these properties.
<PUBLIC SERVICE ANNOUNCEMENT> Many of you probably know this already, but for those who might not know: Prelude> let x = read "NaN" :: Float Prelude> x == x False Prelude> x == 0 False Prelude> 0 < x False Prelude> x < 0 False Ewwwwww! Be careful how far you depend on properties of typeclasses, and make sure you document it when you do. <we now return to you regularly scheduled discussion> Rob Dockins

G'day all.
Quoting Robert Dockins
Ewwwwww! Be careful how far you depend on properties of typeclasses, and make sure you document it when you do.
The behaviour of NaN actually makes perfect sense when you realise that it is Not a Number. Things that are not numbers are incomparable with things that are. Yes, NaN can be of type Float. But it's not a Float. Cheers, Andrew Bromage

On Apr 7, 2006, at 1:36 AM, ajb@spamcop.net wrote:
G'day all.
Quoting Robert Dockins
: Ewwwwww! Be careful how far you depend on properties of typeclasses, and make sure you document it when you do.
The behaviour of NaN actually makes perfect sense when you realise that it is Not a Number. Things that are not numbers are incomparable with things that are.
Yes, NaN can be of type Float. But it's not a Float.
If you take that tack, then you have to concede that the type system isn't doing what it should (keeping me from having something not-a- float where I expect a float). Any way you slice it, its an unfortunate situation. I'd personally rather that any operation generating NaN raises an exception, a la divide by 0 at Int. I think (although I'm not sure) that the floating point infinities play nice wrt equality and ordering, so getting rid of NaN would restore at least _some_ semblance of proper algebraic behavior to the floating point representations. (And the FFI already has CFloat/CDouble, so you should use those when you really need to actually do something with NaN generated by external code, and CFloat/CDobule should not be members of Eq and Ord). Or at the very least, attempting to compare NaN using (==) or (<) and friends should raise an exception, rather than just returning broken results.
Cheers, Andrew Bromage
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Robert Dockins wrote:
The behaviour of NaN actually makes perfect sense when you realise that it is Not a Number. Things that are not numbers are incomparable with things that are.
Yes, NaN can be of type Float. But it's not a Float.
If you take that tack, then you have to concede that the type system isn't doing what it should (keeping me from having something not-a-float where I expect a float). Any way you slice it, its an unfortunate situation.
I'd personally rather that any operation generating NaN raises an exception, a la divide by 0 at Int. I think (although I'm not sure) that the floating point infinities play nice wrt equality and ordering, so getting rid of NaN would restore at least _some_ semblance of proper algebraic behavior to the floating point representations. (And the FFI already has CFloat/CDouble, so you should use those when you really need to actually do something with NaN generated by external code, and CFloat/CDobule should not be members of Eq and Ord).
Or at the very least, attempting to compare NaN using (==) or (<) and friends should raise an exception, rather than just returning broken results.
Rob Dockins
The IEEE 754 standard explicitly specifies that complete implementations can have either or both 'signalling' NaNs and 'quiet' NaNs. It appears that current Haskell implementations have chosen to go with quiet NaNs, which is very surprising indeed, as that does go "against" the type system. Signalling NaNs are more consistent with the rest of Haskell's semantics. However, it is also important to note that IEEE 754 also mandates 'trap handlers' for signalling NaNs, so that implementors may choose (even at run-time, on a per-instance basis) what to do with any given occurence of NaN. In particular, it is possible to resume the computation with a _value_ being substituted in for that NaN. These 'trap handlers' are also in there for division-by-zero, so that one may _choose_ to return either infinity or raise an actual exception. If one reads the standard (IEEE 754) carefully enough, it is possible to 'pick' an implementation of it which actually fits in with Haskell fairly well. Yes, the standard is explicitly written to have *choices* in it for implementors. The current implementation is generally standard-compliant, but does not seem to 'pick' a path of least-resistance wrt the rest of Haskell. Jacques

On Apr 7, 2006, at 9:43 AM, Jacques Carette wrote:
Robert Dockins wrote:
The behaviour of NaN actually makes perfect sense when you realise that it is Not a Number. Things that are not numbers are incomparable with things that are.
Yes, NaN can be of type Float. But it's not a Float.
If you take that tack, then you have to concede that the type system isn't doing what it should (keeping me from having something not-a-float where I expect a float). Any way you slice it, its an unfortunate situation.
I'd personally rather that any operation generating NaN raises an exception, a la divide by 0 at Int. I think (although I'm not sure) that the floating point infinities play nice wrt equality and ordering, so getting rid of NaN would restore at least _some_ semblance of proper algebraic behavior to the floating point representations. (And the FFI already has CFloat/CDouble, so you should use those when you really need to actually do something with NaN generated by external code, and CFloat/CDobule should not be members of Eq and Ord).
Or at the very least, attempting to compare NaN using (==) or (<) and friends should raise an exception, rather than just returning broken results.
Rob Dockins
The IEEE 754 standard explicitly specifies that complete implementations can have either or both 'signalling' NaNs and 'quiet' NaNs. It appears that current Haskell implementations have chosen to go with quiet NaNs, which is very surprising indeed, as that does go "against" the type system. Signalling NaNs are more consistent with the rest of Haskell's semantics.
However, it is also important to note that IEEE 754 also mandates 'trap handlers' for signalling NaNs, so that implementors may choose (even at run-time, on a per-instance basis) what to do with any given occurence of NaN. In particular, it is possible to resume the computation with a _value_ being substituted in for that NaN. These 'trap handlers' are also in there for division-by-zero, so that one may _choose_ to return either infinity or raise an actual exception.
If one reads the standard (IEEE 754) carefully enough, it is possible to 'pick' an implementation of it which actually fits in with Haskell fairly well. Yes, the standard is explicitly written to have *choices* in it for implementors. The current implementation is generally standard-compliant, but does not seem to 'pick' a path of least-resistance wrt the rest of Haskell.
Is this an H' worthy item? Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

On Apr 7, 2006, at 9:43 AM, Jacques Carette wrote:
[Lots of stuff about IEEE 754] Is this an H' worthy item? It is worth taking a serious look in conjunction with completely redoing
Robert Dockins wrote: the Num class. Minor tweaking of the behaviour on NaNs (which requires a large amount of background work) does not seem to be worthwhile on its own (in my not-at-all-humble-opinion, having done this before). If getting the Num class "right" is in the cards for H', which probably presupposes that some kinds of class alias support is also 'in', then looking at a proper implementation of IEEE 754 is worth it. Note that this would also need that arithmetic operators be able to throw signals, which can be either caught and 'handled' or turned (automatically) into exceptions. While 'signals' here can be _completely_ independent from O/S signals, it also intersects with current discussions on exceptions. Right now, I am waiting to see where the dust settles on Num, class aliases and exceptions. If it looks like all these things will happen, then I will throw my hat in to *do* something about proper IEEE 754 support for Float, Double, etc. Jacques

Robert Dockins writes:
On Thursday 06 April 2006 06:44 pm, John Meacham wrote:
On Thu, Apr 06, 2006 at 10:52:52PM +0100, Brian Hulley wrote:
[snip a question about Eq and Ord classes]
well, there are a few reasons you would want to use inheritance in haskell, some good, some bad.
1. one really does logically derive from the other, Eq and Ord are like this, the rules of Eq says it must be an equivalance relation and that Ord defines a total order over that equivalance relation. this is a good thing, as it lets you write code that depends on these properties.
<PUBLIC SERVICE ANNOUNCEMENT>
Many of you probably know this already, but for those who might not know:
Prelude> let x = read "NaN" :: Float Prelude> x == x False Prelude> x == 0 False Prelude> 0 < x False Prelude> x < 0 False
Ewwwwww! Be careful how far you depend on properties of typeclasses, and make sure you document it when you do.
It's worse than that.
Prelude> let x = read "NaN" :: Float
Prelude> compare x x
GT
Prelude> x > x
False
So far as I can tell, report does not actualy *require* that |x > y| iff
|compare x y == GT|, but this is an unfortunate inconsistency.
--
David Menendez

John Meacham wrote:
On Thu, Apr 06, 2006 at 10:52:52PM +0100, Brian Hulley wrote:
[snip] The problem of allowing classes (in Haskell) to inherit is that you end up with heirarchies which fix the design according to some criteria which may later turn out to be invalid, whereas if there were no hierarchies then you could just use the particular classes that are needed for the particular function, eg explicitly supplying Eq and Ord instead of just Ord etc (though for a sort function Ord by itself would be sufficient).
well, there are a few reasons you would want to use inheritance in haskell, some good, some bad.
1. one really does logically derive from the other, Eq and Ord are like this, the rules of Eq says it must be an equivalance relation and that Ord defines a total order over that equivalance relation. this is a good thing, as it lets you write code that depends on these properties.
As Steve and Robert pointed out, you can't always rely on these properties (although it is debatable whether or not floats and doubles have any useful numeric properties in the first place). Also, the use of Ord for sorting comes with extra baggage in the form of a total order whereas you might have just wanted to sort some values of a type where there is only a partial order. Thus the bundling of < > <= >= together, with == being defined in terms of <= seems overly restrictive. [rearranged]
the inflexability of the class hierarchy was my motivation for the class aliases proposal.
What about: class Eq a where (==), (/=) :: ... class PartialOrd a where (<), (>) :: a->a->Bool x > y = y < x class (PartialOrd a) => TotalOrd a where x <= y = not (y < x) .... -- => not meaning inheritance but just a restriction on a for use of TotalOrd class alias Ord a = (Eq a, PartialOrd a, TotalOrd a) -- components of Ord all on the same level Then sort could be declared as sort :: PartialOrd a => [a] -> [a] Changing the subject slightly, a minor problem (no doubt you've already noticed it) is that if you allow instance declarations for class aliases, there is a danger of overlapping instance definitions eg: class Monad m where (>>=) :: ... class alias AliasMonadFirst m (Monad m, First m) class alias AliasMonadSecond m (Monad m, Second m) instance AliasMonadFirst T where x >>= y = DEF1 instance AliasMonadSecond T where x >>= y = DEF2 foo :: AliasMonadFirst a, AliasMonadSecond a => -- problem: conflicting Monad dictionaries for a==T The presence of such overlapping instances might be invisible to the end-user of the aliases (since it depends on how the aliases are bound which is presumably usually hidden to allow later refactoring) This problem doesn't arise at the moment since the instance declaration only allows the non-inherited (ie non-shared) part to be specified (so that foo :: MonadIO a, MonadPlus a => ... always uses the same definitions for Monad even though the identical definitions for Monad are duplicated in the 2 dictionaries)
2. it is more efficient on dictionary passing implementations of typeclasses. (does not apply to typecase based implementations like jhc)
3. it is simpler to declare instances for, the default methods of Ord can depend on Eq.
2) can be solved using aliases or whole program optimization 3) can be solved with aliases
1 is a very good reason.
Only if you are happy with < having to be a total order in every program that will ever be written :-) (Though perhaps I am contradicted by the necessary relationship between TotalOrd and PartialOrd) Regards, Brian.

On 4/6/06, Brian Hulley
What about:
class Eq a where (==), (/=) :: ... class PartialOrd a where (<), (>) :: a->a->Bool x > y = y < x
class (PartialOrd a) => TotalOrd a where x <= y = not (y < x) .... -- => not meaning inheritance but just a restriction on a for use of TotalOrd
A partial order can be defined in either of two ways, both of which require some notion of equality. If it is a weak partial order, you need to require reflexivity, i.e. x=y implies R(x,y). If it is a strong partial order, you need to require irreflexivity. So some notion of equality is necessary in either case. (I think the same is true of preorders, if we want to generalize to that.) So, if such a PartialOrd existed, it really should be between Eq and Ord in the class hierarchy. Steve

Brian Hulley wrote:
John Meacham wrote:
[snip] 1. one really does logically derive from the other, Eq and Ord are like this, the rules of Eq says it must be an equivalance relation and that Ord defines a total order over that equivalance relation. this is a good thing, as it lets you write code that depends on these properties.
As Steve and Robert pointed out, you can't always rely on these properties (although it is debatable whether or not floats and doubles have any useful numeric properties in the first place).
Actually I'm revising my idea about this. I think that Float and Double are just intrinsically dangerous numeric types which have members that don't satisfy the Eq and Ord equations so their presence doesn't contradict your argument in favour of hierarchical classes. It rather suggests that the existing hierarchy where Float and Double are instances of RealFloat which inherits (indirectly) from Ord is simply wrong, since Float and Double don't and can't obey the Ord equations. Perhaps Float and Double should be moved to a class such as DangerousNum which does not inherit from Eq, Ord etc so that it would be clear they can't participate in any equational reasoning? This would require different names for all DangerousNum ops or some way to qualify the name of a class member with the class name eg 3.0 DangerousNum£+ 5.6 (dot can't be used because then DangerousNum would be assumed to be a module name) Stephen Forrest wrote:
On 4/6/06, Brian Hulley
wrote: What about:
class Eq a where (==), (/=) :: ... class PartialOrd a where (<), (>) :: a->a->Bool x > y = y < x
class (PartialOrd a) => TotalOrd a where x <= y = not (y < x) .... -- => not meaning inheritance but just a restriction on a for use of TotalOrd
A partial order can be defined in either of two ways, both of which require some notion of equality. If it is a weak partial order, you need to require reflexivity, i.e. x=y implies R(x,y). If it is a strong partial order, you need to require irreflexivity. So some notion of equality is necessary in either case. (I think the same is true of preorders, if we want to generalize to that.)
So, if such a PartialOrd existed, it really should be between Eq and Ord in the class hierarchy.
It seems that there are indeed some hierarchies that are intrinsic and therefore I'll have to withdraw my attempt to argue in favour of a flat class system! :-) Thanks to all who replied, Brian.

John Meacham wrote:
1. one really does logically derive from the other, Eq and Ord are like this, the rules of Eq says it must be an equivalance relation and that Ord defines a total order over that equivalance relation. this is a good thing, as it lets you write code that depends on these properties.
given an Ord instance (for a type T) a corresponding Eq instance can be given by: instance Eq T where a == b = compare a b == EQ This does not make the definition of an Ord instance (that is supposed to match an equivalence) easier but ensures at least the required consistency. I never dared to define this generically and switch on various ghc extensions: instance Ord a => Eq a where ... It just strikes me that wrt. "NaN" the Ord instances for Float and Double are no total orders (and thus these types are not suited for sets, i.e. "Data.Set.Set Float") Cheers Christian

given an Ord instance (for a type T) a corresponding Eq instance can be given by:
instance Eq T where a == b = compare a b == EQ
where did this second -----^ == come from? (I guess if if Ordering derives Eq :-) I think you meant
instance (Ord T) => Eq T where a == b = case compare a b of EQ -> True _ -> False
Cheers, Jared. -- http://www.updike.org/~jared/ reverse ")-:"

On 4/7/06, Jared Updike
given an Ord instance (for a type T) a corresponding Eq instance can be given by:
instance Eq T where a == b = compare a b == EQ
where did this second -----^ == come from? (I guess if if Ordering derives Eq :-) I think you meant
instance (Ord T) => Eq T where a == b = case compare a b of EQ -> True _ -> False
Both work the same. Here's an intermediate form: a == b = if compare a b == EQ then True else False

On 4/7/06, Jared Updike
given an Ord instance (for a type T) a corresponding Eq instance can be given by:
instance Eq T where a == b = compare a b == EQ
where did this second -----^ == come from? (I guess if if Ordering derives Eq :-) I think you meant
I think another poster essentially already said this, but the second == comes from the Eq instance for type Ordering, which is in the Prelude. So this we can actually rely on. Steve

there has been discussions on and off indicating problems with the structure of the number classes in the prelude. i have found a discussion paper by mechveliani but i have not found a concrete proposal on the haskell' list of tickets. i hope i can advance the process by making a concrete proposal for which i attach Haskell code and a pdf giving the rational can be found at ftp://ftp.geoinfo.tuwien.ac.at/frank/numbersPrelude_v1.pdf if i have not found other contributions, i am sorry and hope to hear about them. i try a conservative structure, which is more conservative than the structure we have used here for several years (or mechveliani's proposal). It suggests classes for units (Zeros, Ones) and CommGroup (for +, -), OrdGroup (for abs and difference), CommRing (for *, sqr), EuclideanRing (for gdc, lcm, quot, rem, div...) and Field (for /). I think the proposed structure could be a foundation for mathematically strict approaches (like mechveliani's) but still be acceptable to 'ordinary users'. i put this proposal for discussion here and hope for suggestions how it can be improved before i put it to haskell'! andrew frank

On Mon, 10 Apr 2006, Andrew U. Frank wrote:
there has been discussions on and off indicating problems with the structure of the number classes in the prelude. i have found a discussion paper by mechveliani but i have not found a concrete proposal on the haskell' list of tickets. i hope i can advance the process by making a concrete proposal for which i attach Haskell code and a pdf giving the rational can be found at ftp://ftp.geoinfo.tuwien.ac.at/frank/numbersPrelude_v1.pdf
if i have not found other contributions, i am sorry and hope to hear about them.
I recently mentioned the NumericPrelude project: http://cvs.haskell.org/darcs/numericprelude/ http://cvs.haskell.org/darcs/numericprelude/src/Algebra/Core.lhs http://cvs.haskell.org/darcs/numericprelude/docs/html/

On Mon, 10 Apr 2006, Andrew U. Frank wrote:
there has been discussions on and off indicating problems with the structure of the number classes in the prelude. i have found a discussion paper by mechveliani but i have not found a concrete proposal on the haskell' list of tickets. i hope i can advance the process by making a concrete proposal for which i attach Haskell code and a pdf giving the rational can be found at ftp://ftp.geoinfo.tuwien.ac.at/frank/numbersPrelude_v1.pdf
Why are Zeros and Ones separated from the classes providing the operations? Since groups are required to have a neutral element and rings must have both a neutral additive element and a neutral multiplicative element, it makes sense to me, to couple Additive group with a zero and a Ring structure with a one. I guess you want to separate them because there are vectors and matrices of different sizes which we subsume under the same Haskell type. I have not seen a convincing solution for this problem so far. Indeed there are proposals implicit parameters, local type class instances and so on. The problem arises also for residue classes. I have worked around that problem by not comparing with a generated zero, but use a special isZero method. If I need a zero or a one in an algorithm I make it a parameter of the algorithm. Sometimes this leads to a nice generalization of an algorithm, if callers provide values different from zero. gcd+lcm, quot+rem, div+mod: In NumericPrelude quot+rem and div+mod are in separate classes. 'quot' and 'rem' need a notion of rounding towards zero. They are less general than 'div' and 'mod'. Actually I have never found an appriopriate application of 'quot' and 'rem'. When I saw them in other programs, 'div' or 'mod' were always the better choice. Also in NP 'gcd' and 'lcm' are separated from 'div' and 'mod', because the greatest common divisor cannot be always computed by the Euclidean algorithm. (^), (^^), (**): I found the distinctions of powers very useful and I would even refine them. In mathematical notation we don't respect types and we do not distinguish between powers of different types. However if we assume the most general types for both basis and exponent, the result of the power is no longer unique. Actually all possible solutions of say 1^x, where x is irrational is dense in the complex unit circle. In the past I needed the power of two complex numbers only once, namely for the Cauchy wavelet: f(t) = (1- i*k*t) ^ (-1/2 + mu2/k + i*mu1) http://www.math.uni-bremen.de/~thielema/Research/cwt.pdf http://ieeexplore.ieee.org/iel5/78/18506/00852022.pdf?arnumber=852022 However, I could not use the built-in complex power function because the resulting function became discontinuous. Of course, powers of complex numbers have the problem of branch cuts and the choice of the branch built into the implementation of the complex power is quite arbitrary and might be inappropriate. But also for real numbers there are problems: For computing (-1)**(1/3::Double) the power implementation has to decide whether (1/3::Double) is close enough to a third. If it does so it returns (-1) otherwise it fails. However, why shall 0.333333333333333 represent 1/3? It may be really meant as 333333333333333/10^15, and a real 10^15th root of (-1) does not exist. So I propose some balancing: The more general the basis the less general the exponent and vice versa. I also think the following symbols are more systematic and intuitive: any ring (provides *) ^ cardinal any field (provides /) ^- integer an algebraic field ^/ rational (computing a list of powers depending on the denominator of the rational) positive real (including transcendent) ^? anything (unqiue via exponential series) That is (^-) would replace (^^), (^?) would replace (**), (^) remains and (^/) is new. Branch cuts are a problem for all functions based on logarithms, apart from log and (**) these are: asin, acos, atan, asinh, acosh, atanh. I wonder how to treat them. I thought whether a residue class type would help. However a residue class with respect to the transcendent number pi would lead to a lot of rounding problems and the residue classes could be hardly processed further. So I'm thinking about a logarithm which returns a list of possible solutions. However for real numbers the logarithm is unique. I come to the conclusion that real logarithms and associated functions are considerably different from there generalizations to complex numbers. How to resolve that in type classes?

On Mon, Apr 10, 2006 at 12:13:55PM +0200, Andrew U. Frank wrote:
there has been discussions on and off indicating problems with the structure of the number classes in the prelude. i have found a discussion paper by mechveliani but i have not found a concrete proposal on the haskell' list of tickets. i hope i can advance the process by making a concrete proposal for which i attach Haskell code and a pdf giving the rational can be found at ftp://ftp.geoinfo.tuwien.ac.at/frank/numbersPrelude_v1.pdf
if i have not found other contributions, i am sorry and hope to hear about them.
i try a conservative structure, which is more conservative than the structure we have used here for several years (or mechveliani's proposal). It suggests classes for units (Zeros, Ones) and CommGroup (for +, -), OrdGroup (for abs and difference), CommRing (for *, sqr), EuclideanRing (for gdc, lcm, quot, rem, div...) and Field (for /). I think the proposed structure could be a foundation for mathematically strict approaches (like mechveliani's) but still be acceptable to 'ordinary users'.
I agree with Henning Thielemann about putting 'zero' in 'CommGroup' and 'one' in 'CommRing'. What is your thinking here? I would also argue for putting 'fromInteger' in 'CommRing', as discussed in the NumPrelude proposal. 'EuclideanRing' is a misnomer; a Euclidean Ring is a particular type of ring where GCD, etc. can be defined (see http://planetmath.org/encyclopedia/EuclideanRing.html), but there are other such rings, namely any Principal Ideal Domain or PID. 'IntegralDomain' is also a misnomer; I don't know what you're getting at there, but there is a well-established mathematical term 'integral domain' that means something different. o On enforcing properties: there's not currently any way to enforce properties (e.g., monad laws are not enforced); however, I believe that expected properties should be documented. o ^ and ^^ (which can actually be combined, see our proposal) are in fact quite useful, and can be implemented considerably more efficiently than a general exponentiation. If you want a complete proposal, you do need to go further. o You do impose some additional burden by changing the name of the 'Num' class, and it is worth noting that. o Mechvelliani's implementation could not be built on top of your base, because he needs to have a sample argument to 'zero' to determine, e.g., the right zero for modular arithmetic. Henning mentioned this in his response. To implement modular arithmetic with these signatures, as far as I know, you need to either separate Zero constructors or do something like the Kiselyov-Shan paper. (See, e.g., Frederick Eaton's linear algebra library recently posted to the Haskell list.) Peace, Dylan Thurston

On Thu, 6 Apr 2006 21:31:24 +0100, you wrote:
I've been wondering for a long time if there is a reason why Ord should inherit from Eq and not vice versa, or whether in fact there is any justification for making either Ord or Eq inherit from the other one.
Support for the concept of equality/inequality does NOT imply the existence of an absolute ordering. For example, identical twins can be considered to be "equal" to each other, and "not equal" to any other person, while persons who are not half of an identical twin pair are "not equal" to all other persons. (For simplicity, I've ignored the existence of identical triplets, quadruplets, etc.) For an example that's perhaps a bit closer to home, consider modulo arithmetic (or any other cyclic group). Another example is the definition of NaN (not-a-number) comparisons in the IEEE floating-point arithmetic standard: If you have two operands, where at least one of them is a NaN, then ==, >, <, <= and >= all return False, while /= returns True. On the other hand, while I suppose it's conceivable to have a situation where there is an absolute ordering but no equality/inequality, it puts you in the awkward position of not being able to compare something to itself. Steve Schafer Fenestra Technologies Corp. http://www.fenestra.com/
participants (14)
-
ajb@spamcop.net
-
Andrew U. Frank
-
Brian Hulley
-
Christian Maeder
-
David Menendez
-
Dylan Thurston
-
Henning Thielemann
-
ihope
-
Jacques Carette
-
Jared Updike
-
John Meacham
-
Robert Dockins
-
Stephen Forrest
-
Steve Schafer