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

2001-02-11 Thread Marcin 'Qrczak' Kowalczyk

Sun, 11 Feb 2001 13:37:28 +1300, Brian Boutel [EMAIL PROTECTED] pisze:

 Can you demonstrate a revised hierarchy without Eq? What would
 happen to Ord and the numeric classes with default class method
 definitions that use (==) either explicitly or in pattern matching
 against numeric literals?

OK, then you can't write these default method definitions.

I'm against removing Eq from the numeric hierarchy, against making Num
instances for functions, but I would probably remove Show. I haven't
seen a sensible proposal of a replacement of the whole hierarchy.

 In an instance declaration, if a method requires operations of
 another class which is not a superclass of the class being instanced,
 it is sufficient to place the requirement in the context,

Better: it is sufficient if the right instance is defined somewhere.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTPCZA
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-11 Thread William Lee Irwin III

Sun, 11 Feb 2001 13:37:28 +1300, Brian Boutel [EMAIL PROTECTED] pisze:
 Can you demonstrate a revised hierarchy without Eq? What would
 happen to Ord and the numeric classes with default class method
 definitions that use (==) either explicitly or in pattern matching
 against numeric literals?

I anticipate that some restructuring of the numeric classes must be
done in order to accomplish this. I am, of course, attempting to
contrive such a beast for my own personal use.

On Sun, Feb 11, 2001 at 07:59:38AM +, Marcin 'Qrczak' Kowalczyk wrote:
 OK, then you can't write these default method definitions.
 I'm against removing Eq from the numeric hierarchy, against making Num
 instances for functions, but I would probably remove Show. I haven't
 seen a sensible proposal of a replacement of the whole hierarchy.

Well, there are a couple of problems with someone like myself trying
to make such a proposal. First, I'm a bit too marginalized and/or
committed to a radical alternative. Second, I don't have the right
associations or perhaps other resources.

Removing Eq sounds like a good idea to me, in all honesty, though I
think numeric instances for functions (at least by default) aren't
great ideas. More details follow:

Regarding Eq, there are other types besides functions which might
not be good ideas to define equality on, either because they're not
efficiently implementable or are still inappropriate. Matrix types
aren't good candidates for defining equality, for one. Another one
you might not want to define equality on are formal power series
represented by infinite lists, since equality tests will never
terminate. A third counterexample comes, of course, from graphics,
where one might want to conveniently scale and translate solids.
Testing meshes and surface representations for equality is once
again not a great idea. Perhaps these counterexamples are a little
contrived, but perhaps other people can come up with better ones.

As far as the function instances of numeric types, there are some
nasty properties that they have that probably make it a bad idea.
In particular, I discovered that numeric literals' fromInteger
property creates the possibility that something which is supposed
to be a scalar or some other numeric result might accidentally be
applied. For instance, given an expression with an intermediate
numeric result like:

f u v . g x y $ h z

which is expected to produce a number, one could accidentally apply
a numeric literal or something bound to one to some arguments, creating
a bug. So this is for at least partial agreement, though I think it
should be available in controlled circumstances. Local module
importations and/or scoped instances might help here, or perhaps
separating out code that relies upon them into a module where the
instance is in scope, as it probably needs control which is that tight.

Sun, 11 Feb 2001 13:37:28 +1300, Brian Boutel [EMAIL PROTECTED] pisze:
 In an instance declaration, if a method requires operations of
 another class which is not a superclass of the class being instanced,
 it is sufficient to place the requirement in the context,

On Sun, Feb 11, 2001 at 07:59:38AM +, Marcin 'Qrczak' Kowalczyk wrote:
 Better: it is sufficient if the right instance is defined somewhere.

Again, I'd be careful with this idea. It's poor design to unnecessarily
restrict the generality of code. Of course, it's poor design to not try
to enforce necessary conditions in the type system, too, which is why
library design is nontrivial. And, of course, keeping it simple enough
for use by the general populace (or whatever semblance thereof exists
within the Haskell community) might well conflict with the desires of
persons like myself who could easily fall prey to the accusation that
they're trying to turn Haskell into a computer algebra system, and adds
yet another constraint to the library design making it even tougher.


Cheers,
Bill

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-11 Thread Brian Boutel

Marcin 'Qrczak' Kowalczyk wrote:


 I'm against removing Eq from the numeric hierarchy, against making Num
 instances for functions, but I would probably remove Show. I haven't
 seen a sensible proposal of a replacement of the whole hierarchy.
 

Then we probably are in agreement. 

--brian

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-11 Thread William Lee Irwin III

On 11-Feb-2001, Brian Boutel [EMAIL PROTECTED] wrote:
 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 [EMAIL PROTECTED] wrote:
 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-10 Thread Brian Boutel

Marcin 'Qrczak' Kowalczyk wrote:
 
 Sat, 10 Feb 2001 14:09:59 +1300, Brian Boutel [EMAIL PROTECTED] pisze:
 
  Can you demonstrate a revised hierarchy without Eq? What would happen to
  Ord, and the numeric classes that require Eq because they need signum?
 
 signum doesn't require Eq. You can use signum without having Eq, and
 you can sometimes define signum without having Eq (e.g. on functions).
 Sometimes you do require (==) to define signum, but it has nothing to
 do with superclasses.
 

Let me restate my question more carefully:

Can you demonstrate a revised hierarchy without Eq? What would happen to
Ord and the numeric classes with default class method definitions that
use (==) either explicitly or in pattern matching against numeric
literals? Both Integral and RealFrac do this to compare or test the
value of signum.

In an instance declaration, if a method requires operations of another
class which is not a superclass of the class being instanced, it is
sufficient to place the requirement in the context, but for default
class method definitions, all class methods used must belong to the
class being defined or its superclasses.


--brian

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-10 Thread Brian Boutel

Fergus Henderson wrote:
 
 On 09-Feb-2001, Brian Boutel [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-10 Thread Fergus Henderson

On 11-Feb-2001, Brian Boutel [EMAIL PROTECTED] wrote:
 Fergus Henderson wrote:
  
  On 09-Feb-2001, Brian Boutel [EMAIL PROTECTED] 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 [EMAIL PROTECTED]  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-09 Thread Ketil Malde

Brian Boutel [EMAIL PROTECTED] writes:

 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 think there is.  If I design a class and derive it from Num with
(==) is bottom, I am allowed to apply to it functions requiring a Num
argument, but I have no guarantee it will work.

The implementor of that function can change its internals (to use
(==)), and suddenly my previously working program is non-terminating. 
If I defined (==) to give a run time error, it'd be a bit better, but
I'd much prefer the compiler to tell me about this in advance.

 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:

It's not about "needing to apply", but about finding a reasonable
definition. 

 - Having a class hierarchy at all (or making any design decision)
 implies compromise.

I think the argument is that we should move Eq and Show *out* of the
Num hierarchy.  Less hierarchy - less compromise.

 - The current hierarchy (and its predecessors) represent a reasonable
 compromise that meets most needs.

Obviously a lot of people seem to think we could find compromises that
are more reasonable.

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

Isn't it a good idea to reduce the amount of pain?

 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.

I don't think syntax is unimportant.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-09 Thread Brian Boutel

Ketil Malde wrote:
 
 Brian Boutel [EMAIL PROTECTED] writes:
 
  - Having a class hierarchy at all (or making any design decision)
  implies compromise.
 
 I think the argument is that we should move Eq and Show *out* of the
 Num hierarchy.  Less hierarchy - less compromise.


Can you demonstrate a revised hierarchy without Eq? What would happen to
Ord, and the numeric classes that require Eq because they need signum? 


 
  - The current hierarchy (and its predecessors) represent a reasonable
  compromise that meets most needs.
 
 Obviously a lot of people seem to think we could find compromises that
 are more reasonable.

I would put this differently. "A particular group of people want to
change the language to make it more convenient for their special
interests."

 
  - 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,
 
 Isn't it a good idea to reduce the amount of pain?

Not always.

 
  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.
 
 I don't think syntax is unimportant.


I wrote that *concrete* syntax is ultimately unimportant, not *syntax*.
There is a big difference. In particular, *lexical syntax*, the choice
of marks on paper used to represent a language element, is not
important, although it does give rise to arguments, as do all mattters
of taste and style.

Thre are not enough usable operator symbols to go round, so they get
overloaded. Mathematicians have overloaded common symbols like (+) and
(*) for concepts that have may some affinity with addition and
multiplication in arithmetic, but which are actually quite different.
That's fine, because, in context, expert human readers can distinguish
what is meant. From a software engineering point of view, though, such
free overloading is dangerous, because readers may assume, incorrectly,
that an operator has properties that are typically associated with
operators using that symbol. This may not matter in a private world
where the program writer is the only person who will see and use the
code, and no mission-critial decisions depend on the results, but it
should not be the fate of Haskell to be confined to such use.

Haskell could have allowed free ad hoc overloading, but one of the first
major decisions made by the Haskell Committee in 1988 was not to do so.
Instead, it adopted John Hughes' proposal to introduce type classes to
control overloading. A symbol could only be overloaded if the whole of a
group of related symbols (the Class) was overloaded with it, and the
class hierarchy provided an even stronger constraint by restricting
overloading of the class operators to cases where other classes,
intended to be closely related, were also overloaded. This tended to
ensure that the new type at which the classes were overloaded had strong
resemblences to the standard types. Simplifying the hierarchy weakens
these constraints and so should be approached with extreme caution. Of
course, the details of the classes and the hierarchy have changed over
the years - there is, always has been and always will be pressure to
make changes to meet particular needs - but the essence is still there,
and the essence is of a general-purpose language, not a domain-specific
language for some branches of mathematics.

A consequence of this is that certain uses of overloaded symbols are
inconvenient, because they are too far from the mainstream intended
meaning. If you have such a use, and you want to write in Haskell, you
have to choose other lexical symbols to represent your operators. You
make your choice.

--brian

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-09 Thread Fergus Henderson

On 09-Feb-2001, Brian Boutel [EMAIL PROTECTED] 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.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-09 Thread Marcin 'Qrczak' Kowalczyk

Sat, 10 Feb 2001 14:09:59 +1300, Brian Boutel [EMAIL PROTECTED] pisze:

 Can you demonstrate a revised hierarchy without Eq? What would happen to
 Ord, and the numeric classes that require Eq because they need signum? 

signum doesn't require Eq. You can use signum without having Eq, and
you can sometimes define signum without having Eq (e.g. on functions).
Sometimes you do require (==) to define signum, but it has nothing to
do with superclasses.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTPCZA
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-07 Thread Jerzy Karczmarczuk

"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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe