Re: Revamping the numeric classes

2001-02-07 Thread Ch. A. Herrmann

moved to haskell-cafe

Ketil E.g. way back, I wrote a simple differential equation solver.
Ketil Now, the same function *could* have been applied to vector
Ketil functions, except that I'd have to decide on how to implement
Ketil all the "Num" stuff that really didn't fit well.  Ideally, a
Ketil nice class design would infer, or at least allow me to
Ketil specify, the mathematical constraints inherent in an
Ketil algorithm, and let my implementation work with any data
Ketil satisfying those constraints.

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 "*".

A cheap solution could be to define a type MathObject and operators like 
   :*: MathObject - MathObject - MathObject
Then, the user can implement:

a :*: b = case (a,b) of
 (Matrix x, Matrix y) - foo
 (Matrix x, Vector y) - bar
-- 
 Christoph Herrmann
 E-mail:  [EMAIL PROTECTED]
 WWW: http://brahms.fmi.uni-passau.de/cl/staff/herrmann.html

___
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



(no subject)

2001-02-07 Thread Dylan Thurston



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



Re: Revamping the numeric classes

2001-02-07 Thread Marcin 'Qrczak' Kowalczyk

07 Feb 2001 11:47:11 +0100, Ketil Malde [EMAIL PROTECTED] pisze:

 If it is useful to have a fine granularity of classes, you can
 imagine doing:
 
 class Multiplicative a b c where
 (*) :: a - b - c

Then a*b*c is ambiguous no matter what are types of a,b,c and the
result. Sorry, this does not work. Too general is too bad, it's
impossible to have everything at once.

-- 
 __("  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: Revamping the numeric classes

2001-02-07 Thread Dylan Thurston

Other people have been making great points for me.  (I particularly
liked the example of Dollars as a type with addition but not
multiplication.)  One point that has not been made: given a class
setup like

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

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

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

then naive users can continue to use (Num a) in contexts, and the same
programs will continue to work.[1]

(A question in the above context is whether the literal '0' should be
interpreted as 'fromInteger (0::Integer)' or as 'zero'.  Opinions?)

On Wed, Feb 07, 2001 at 06:27:02PM +1300, 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.

Why doesn't your argument show that all types should by instances of
Eq and Show?  Why are numeric types special?

Best,
Dylan Thurston

Footnotes: 
[1]  Except for the lack of abs and signum, which should be in some
other class.  I have to think about their semantics before I can say
where they belong.



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



Re: Revamping the numeric classes

2001-02-07 Thread andrew

On Wed, Feb 07, 2001 at 11:47:11AM +0100, Ketil Malde wrote:
 "Ch. A. Herrmann" [EMAIL PROTECTED] writes:
[...]
  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.
 Yes, obviously.  On the other hand, I think you could get far by
 defining (+) as an operator in a Group, (*) in a Ring, and so forth.

As a complete newbie can I add a few points?  They may be misguided,
but they may also help identify what appears obvious only through
use...

- understanding the hierarchy of classes (ie constanly referring to
Fig 5 in the report) takes a fair amount of effort.  It would have
been much clearer for me to have classes that simply listed the
required super classes (as suggested in an earlier post).

- even for me, no great mathematician, I found the forced inclusion of
certain classes irritating (in my case - effectively implementing
arithmetic on tuples - Enum made little sense and ordering is hacked
in order to be total; why do I need to define either to overload "+"?)

- what's the deal with fmap and map?

 Another problem is that the mathematical constructs include properties
 not easily encoded in Haskell, like commutativity, associativity, etc.
 
  I don't think that it is acceptable for a language like Haskell
  to permit the user to overload predefined operators, like "*".

Do you mean that the numeric classes should be dropped or are you
talking about some other overloading procedure?

Isn't one popular use of Haskell to define/extend it to support small
domain-specific languages?  In those cases, overloading operatores via
the class mechanism is very useful - you can give the user concise,
but stll understandable, syntax for the problem domain.

I can see that overloading operators is not good in general purpose
libraries, unless carefully controlled, but that doesn't mean it is
always bad, or should always be strictly controlled.  Maybe the
programmer could decide what is appropriate, faced with a particular
problem, rather than a language designer, from more general
considerations?  Balance, as ever, is the key :-)

[...]
 From experience, I guess there are probably issues that haven't
 crossed my mind.   :-)

This is certainly true in my case - I presumed there was some deep
reason for the complex hierarchy that exists at the moment.  It was a
surprise to see it questioned here.

Sorry if I've used the wrong terminology anywhere.  Hope the above
makes some sense.

Andrew

-- 
http://www.andrewcooke.free-online.co.uk/index.html


- End forwarded message -

-- 
http://www.andrewcooke.free-online.co.uk/index.html

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



RE: Revamping the numeric classes

2001-02-07 Thread Peter Douglass

 I have some questions about how Haskell's numeric classes might be
revamped.

 Is it possible in Haskell to circumscribe the availability of certain
"unsafe" numeric operations such as div, /, mod?  If this is not possible
already, could perhaps a compiler flag "-noUnsafeDivide" could be added to
make such a restriction?

 What I have in mind is to remove division by zero as an untypable
expression.  The idea is to require div, /, mod to take NonZeroNumeric
values in their second argument.  NonZeroNumeric values could be created by
functions of type: 
  Number a = a - Maybe NonZeroNumeric
or something similar.

  Has this been tried and failed?  I'm curious as to what problems there
might be with such an approach.

--PeterD  

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



Re: Revamping the numeric classes

2001-02-07 Thread Tom Pledger

Dylan Thurston writes:
 :
 | (A question in the above context is whether the literal '0' should
 | be interpreted as 'fromInteger (0::Integer)' or as 'zero'.
 | Opinions?)

Opinions?  Be careful what you wish for.  ;-)

In a similar discussion last year, I was making wistful noises about
subtyping, and one of Marcin's questions

http://www.mail-archive.com/haskell-cafe@haskell.org/msg00125.html

was whether the numeric literal 10 should have type Int8 (2's
complement octet) or Word8 (unsigned octet).  At the time I couldn't
give a wholly satisfactory answer.  Since then I've read the oft-cited
paper "On Understanding Types, Data Abstraction, and Polymorphism"
(Cardelli  Wegner, ACM Computing Surveys, Dec 1985), which suggests a
nice answer: give the numeric literal 10 the range type 10..10, which
is defined implicitly and is a subtype of both -128..127 (Int8) and
0..255 (Word8).

The differences in arithmetic on certain important range types could
be represented by multiple primitive functions (or perhaps foreign
functions, through the FFI):

primAdd   :: Integer - Integer - Integer-- arbitrary precision
primAdd8s :: Int8- Int8- Int8   -- overflow at -129, 128
primAdd8u :: Word8   - Word8   - Word8  -- overflow at -1, 256
-- etc.

instance Additive Integer where
zero = 0
(+)  = primAdd

...with similar instances for the integer subrange types which may
overflow.  These other instances would belong outside the standard
Prelude, so that the ambiguity questions don't trouble people (such as
beginners) who don't care about the space and time advantages of fixed
precision integers.

Subtyping offers an alternative approach to handling arithmetic
overflows:
  - Use only arbitrary precision arithmetic.
  - When calculated result *really* needs to be packed into a fixed
precision format, project it (or treat it down, etc., whatever's
your preferred name), so that overflows are represented as
Nothing.

For references to other uses of  class Subtype  see:

http://www.mail-archive.com/haskell@haskell.org/msg07303.html

For a reference to some unification-driven rewrites, see:

http://www.mail-archive.com/haskell@haskell.org/msg07327.html

Marcin 'Qrczak' Kowalczyk writes:
 :
 | Assuming that Ints can be implicitly converted to Doubles, is the
 | function
 | f :: Int - Int - Double - Double
 | f x y z = x + y + z
 | ambiguous? Because there are two interpretations:
 | f x y z = realToFrac x + realToFrac y + z
 | f x y z = realToFrac (x + y) + z
 | 
 | Making this and similar case ambiguous means inserting lots of explicit
 | type signatures to disambiguate subexpressions.
 | 
 | Again, arbitrarily choosing one of the alternatives basing on some
 | set of weighting rules is dangerous,

I don't think the following disambiguation is too arbitrary:

x + y + z -- as above

-- (x + y) + z   -- left-associativity of (+)

-- realToFrac (x + y) + z-- injection (or treating up) done
  -- conservatively, i.e. only where needed

Regards,
Tom

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