[Haskell-cafe] Re: Numeric type classes

2006-09-20 Thread Aaron Denney
On 2006-09-20, Jacques Carette <[EMAIL PROTECTED]> wrote:
> [Hopefully this answers your 'relevance' question].

Yes.  I was focusing on the more narrow aspect, rather than what had
started this thread.

> In other words, the "specification language" people have been down this 
> road quite some time ago, and seem to have worked out a fair bit of it.  
> PL people should now liberally borrow all these good ideas IMNSHO.

Thank you for the references.

-- 
Aaron Denney
-><-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-20 Thread Jacques Carette


Whenever people start discussing the Numeric type classes, the true 
scope of what a refactoring can (and should?) be is frequently 
under-estimated.  The 'structure' of algebraic objects in mathematics 
has been studied quite a lot (in mathematics and in CS, but not so much 
by programming language people it seems).  So I point out work like

http://www-sop.inria.fr/cafe/Manuel.Bronstein/libaldor/html/
which already has a richer set of "type classes", and that's just 
Aldor's "prelude".  When you get going, you get the Algebra library

(http://www-sop.inria.fr/cafe/Manuel.Bronstein/algebra/)
which is _huge_.  And most of the discussion on Numeric has been around 
the algebraic (Monoid, Ring, Normed, etc) structures that Numeric right 
now 'hides'.

[Hopefully this answers your 'relevance' question].


Computer programming is of course extremely nominal to provide
abstraction and seperation of concerns.  Yes, anonymous functions are
handy, but I could give them up if I had named local functions.
Yes, you can even go to unlambda and only use combinators.  Practically
we find names extremely useful.
  
I am NOT arguing for no names!  I also like names.  What I am arguing 
for is to

a) be able to use names whenever convenient
and more importantly
b) be able to provide _renamings_ when previously chosen names are 
_inconvenient_.
In many ways, this is what ML's "with type foo = bar" qualifiers allow 
you to do to a certain extent when putting together modules/functors.


It is also the basic idea behind the Adaptor and the Proxy patterns in 
OO.  All these solve the same problem: how do you get around the issue 
that names in a module/class/whatever have been chosen in one way, and 
you need to use them in another.


Various algebraic specification languages have 
thus adopted this too, so that you are not forced to give unique names 
to all your concepts, you can in fact give them meaningful names 'in 
context', and use a remapping when you want to say that you obey a 
particular interface.



This sounds neat, but I'd be worried about how cumbersome it was in
practice.
  
In practice, name clashes do not appear that often, so unique names are 
quite common.  Name clashes tend to appear only for the most basic 
concepts that are highly polymorphic (like Monoid and Group!).  But the 
same happens with generalized Container data-structures too (you can 
'push' onto both a Stack and a Queue, but might want to use different 
names even though the concepts are essentially the same).


It appears to work quite well.  See Specware
http://www.specware.org/index.html
and many of the splendid papers available at
http://www.kestrel.edu/home/publications/

Another line of work is Maude (http://maude.cs.uiuc.edu/), with explicit 
renamings

http://maude.cs.uiuc.edu/maude2-manual/html/node78.html
and more importantly VIEWs
http://maude.cs.uiuc.edu/maude2-manual/html/node81.html
(which have been talked about a lot on the various Haskell mailing 
lists, but Maude has had it implemented for quite some time).


There are plenty of others, like CASL (http://www.cofi.info/CASL.html) 
and the OBJ family (http://cseclassic.ucsd.edu/~goguen/sys/obj.html) 
with similar features.


In other words, the "specification language" people have been down this 
road quite some time ago, and seem to have worked out a fair bit of it.  
PL people should now liberally borrow all these good ideas IMNSHO.



Thanks.  The ML interface paper looks quite interesting.  Are you aware
of any implementations?
  
No - but pressure is slowly building to do so.  It is not an easy task, 
but as the Ocaml developers themselves are discovering as they are 
heavily 'functorising' some of their legacy code, there is a real need.  
I would be willing to believe that if there was a real push to use 
common type classes across GHC/Hugs/nhc/etc, the same phenomenon would 
'appear'.


Jacques
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-20 Thread Aaron Denney
On 2006-09-12, Jacques Carette <[EMAIL PROTECTED]> wrote:
> First, as already pointed out in
> http://www.haskell.org/pipermail/haskell-cafe/2006-April/015404.html
> there is a lot of relevant previous work in this area.

I'm afraid I don't see the relevance.

> This is very easy to do in 'raw' category theory, as concepts are not 
> _nominal_, so a functor from one type to another can explicitly do a 
> renaming if necessary.

Computer programming is of course extremely nominal to provide
abstraction and seperation of concerns.  Yes, anonymous functions are
handy, but I could give them up if I had named local functions.
Yes, you can even go to unlambda and only use combinators.  Practically
we find names extremely useful.

> Various algebraic specification languages have 
> thus adopted this too, so that you are not forced to give unique names 
> to all your concepts, you can in fact give them meaningful names 'in 
> context', and use a remapping when you want to say that you obey a 
> particular interface.

This sounds neat, but I'd be worried about how cumbersome it was in
practice.

> This is an old conversation, see
> http://www.haskell.org/pipermail/haskell/2005-October/016621.html
> for example.

Thanks.  The ML interface paper looks quite interesting.  Are you aware
of any implementations?

-- 
Aaron Denney
-><-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-20 Thread Aaron Denney
On 2006-09-12, Brian Hulley <[EMAIL PROTECTED]> wrote:
> Bryan Burgers wrote:
>> That being said, I'll have to play the other side of the coin: it
>> would probably be a little bit of a pain to have to define instances
>> of each data declaration (Integer, Int, Float, Matrix, Complex, etc.)
>> on each of these seperate classes--especially when being in a certain
>> class usually implies being in another (ie, the definition of a set
>> being a field requires that that set is a group, right?)
>
> Aaron Denney wrote:
>> On 2006-09-12, Bryan Burgers <[EMAIL PROTECTED]> wrote:
>>> And another problem I can see is that, for example, the Integers are
>>> a group over addition, and also a group over multiplication;
>> 
>> Not over multiplication, no, because there is no inverse.
>> 
>> I know of no good way to express that a given data type obeys the
>> same interface two (or more) ways.  Some OO languages try to handle
>> the case of of an abstract base class being inherited twice through
>> two different intermediate classes, but none of them do it well.
>
> How about:
>
> data Multiply = Multiply
> data Add = Add
>
> class Group c e where
> group :: c -> e -> e -> e
> identity :: c -> e
> inverse :: c -> e -> e
>
> instance Group Multiply Rational where
> group Multiply x y = ...
> identity Multiply = 1
> inverse Multiply x = ...
>
> instance Group Add Rational where
> group Add x y = ...
> identity Add = 0
> inverse Add x = ...
>
> (+) :: Group Add a => a -> a -> a
> (+) = group Add
>
> (*) = group Multiply
>
> class (Group Multiply a, Group Add a) => Field a where ...

It's not horrible, but it's somewhat cumbersome, much like passing
around dictionaries explicitly is.

-- 
Aaron Denney
-><-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-15 Thread Henning Thielemann

On Thu, 14 Sep 2006, David Menendez wrote:

> Ross Paterson writes:
> 
> > On Thu, Sep 14, 2006 at 01:11:56AM -0400, David Menendez wrote:
> > > Coincidentally, I spent some time last week thinking about a
> > > replacement for the Num class. I think I managed to come up with
> > > something that's more flexible than Num, but still mostly
> > > comprehensible.
> > 
> > The fact that the first part of your structure is much the same as
> > the one on the web page (which is essentially that part of the revised
> > numeric prelude plus a Haskell 98-compatible veneer) is evidence that
> > it's pretty clear what to do with Num and Fractional.
> 
> That being said, I don't expect anything to change.
> 
> I've looked through the revised numeric prelude, but the qualified class
> names put me off.

Just consequent usage of:
  http://www.haskell.org/hawiki/UsingQualifiedNames

> Everything shows up in Haddock as "C".

That's a problem. I recently tried to extend Haddock to showing
qualifications. But this turned out to be more complicated than I
expected.

> Also, it doesn't support naturals--which, admittedly, is not a big loss.

Simple to add. It will certainly be added.

> > The only point of contention is whether to factor out monoid and
> > semiring classes.  Arguments against include:
> > 
> >  * There are lots of monoids, and (+) doesn't seem a reasonable symbol
> >for some of them.
> 
> True enough. (At least it's more general than "mappend".)
> 
> I would expect all the more specific monoid operators, like (||) and
> (++), to stick around for readability when not writing
> non-monoid-generic code. Not to mention that (+) and (++) associate
> differently.

I think we should separate the names of the functions which implement some
operation from the method names. That is, (||) should be the name for the
implementation of Bool-OR, and could also be 'or' (if this wouldn't be
given to the list function) and (+) is the name of the corresponding
Monoid method. If I want to write a generic monoid algorithm I have to use
(+), otherwise I use (||) for type safety. It's just the same like 'map'
and 'fmap'. However writing accidentally (a+b) if a and b are Bool will no
longer be reported as type error.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-14 Thread Jacques Carette



[EMAIL PROTECTED] wrote:
That is what polymorphism is all about! 


Not in this context, sorry. This is a convention. Another one may give 
you

an abomination, e.g., 1+sin means 1 plus the addres of the sin routine.
(Of course not in a 'decent' language, but I know a few undecent.


No, it is much more than convention.  In this case, it can be made 
completely formal.  The paper I referred to offers one way to do this.  
I sketched another.


Yes, it is possible to have 1+sin become meaningless in 'indecent' 
languages.  But as the mathematics (and Maple and ...) convention shows, 
there is one reasonable way to make this make sense which turns out to 
be quite useful.  In other words, the convention can be turned into a rule.


ML and Haskell have (thankfully) learned a lot from Lisp and Scheme, and 
then proceeded to 'tame' these with static typing.  And this is 
continuing - witness the flurry of type-theoretical research on 
continuations in the last 15 years (and very recent papers on typed 
delimited continuations).  More recently, GADTs have added to the set of 
'safe' programs that can by typed (which Lisp programmers writing 
interpreters knew all along).  I am saying that the case of 'adding 
arrows to the left' is another safe practice.  I backed myself up with a 
published reference [ie I took your comment regarding some of my 
previous haskell-cafe postings seriously!].


Jacques
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-14 Thread jerzy . karczmarczuk
Jacques Carette after David Menendez ... : 

... 


It gets worse than that. Imagine trying to explain to someone why "1 +
sin" is actually "\a -> const 1 a + sin a". 

It isn't that hard - it is done routinely in mathematics courses.  In 
fact, that is what 1+sin means in Maple today (and has for 25 years).  It 
is also what it means in MuPAD.  


Actually in Maple 1 + sin means 1+sin. Of course, you may write
a:=1+sin;
a(5);
and get 1+sin(5), but replacing "sin" by "jacques" gives Maple a very
similar behaviour. This is just a symbolic, *NOT* a functional object!
(And somehow I am sure that you know that...) MuPAD behaves identically. 

That is what polymorphism is all about! 


Not in this context, sorry. This is a convention. Another one may give you
an abomination, e.g., 1+sin means 1 plus the addres of the sin routine.
(Of course not in a 'decent' language, but I know a few undecent. 



Jerzy Karczmarczuk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-14 Thread Jacques Carette

David Menendez wrote:

 * Having (+) work on lists, tuples and all the other monoids would
   make error messages more complicated.



It gets worse than that. Imagine trying to explain to someone why "1 +
sin" is actually "\a -> const 1 a + sin a".
  
It isn't that hard - it is done routinely in mathematics courses.  In 
fact, that is what 1+sin means in Maple today (and has for 25 years).  
It is also what it means in MuPAD.  AFAIK, that is also what 1+Sin means 
in Mathematica.  That is what polymorphism is all about! [This is really 
equational-theory polymorphism rather than parametric polymorphism, but 
that's a minor detail, since Monad polymorphism is _also_ 
equational-theory polymorphism].


This kind of polymorphism [where you add the 'right number' of arrows on 
the left] is quite useful.  Things like differential operators become 
quite tiresome to write down if you have to pedantically spell 
everything out, even though there is only one 'sensible' way to 
interpret a given expression [1].


In the very same way that fromInteger can project a literal integer into 
other typeclasses, one can project values into spaces of functions by 
just "adding arrows on the left" (ie exactly what const does).  It is 
possible to make this quite formal, but you need Natural(s) (as an 
additive monoid) on the type level, and then be able to be polymorphic 
over _those_ to do make it all work.  It should even be decidable [but 
that part I have not checked].  Something I should write up one of these 
days, but in the meantime go read [1]!


Jacquces

[1] Bjorn Lisper and Claes Thomberg have already investigated something 
very close to this, see

http://www.mrtc.mdh.se/index.php?choice=publications&id=0245
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-14 Thread David Menendez
Ross Paterson writes:

> On Thu, Sep 14, 2006 at 01:11:56AM -0400, David Menendez wrote:
> > Coincidentally, I spent some time last week thinking about a
> > replacement for the Num class. I think I managed to come up with
> > something that's more flexible than Num, but still mostly
> > comprehensible.
> 
> The fact that the first part of your structure is much the same as
> the one on the web page (which is essentially that part of the revised
> numeric prelude plus a Haskell 98-compatible veneer) is evidence that
> it's pretty clear what to do with Num and Fractional.

That being said, I don't expect anything to change.

I've looked through the revised numeric prelude, but the qualified class
names put me off. Everything shows up in Haddock as "C". Also, it
doesn't support naturals--which, admittedly, is not a big loss.

> The only point of contention is whether to factor out monoid and
> semiring classes.  Arguments against include:
> 
>  * There are lots of monoids, and (+) doesn't seem a reasonable symbol
>for some of them.

True enough. (At least it's more general than "mappend".)

I would expect all the more specific monoid operators, like (||) and
(++), to stick around for readability when not writing
non-monoid-generic code. Not to mention that (+) and (++) associate
differently.

>  * Having (+) work on lists, tuples and all the other monoids would
>make error messages more complicated.

It gets worse than that. Imagine trying to explain to someone why "1 +
sin" is actually "\a -> const 1 a + sin a".

On the other hand, tuples could be made an instance of Num right now.
-- 
David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws
  |of thermodynamics!"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-14 Thread Ross Paterson
On Thu, Sep 14, 2006 at 01:11:56AM -0400, David Menendez wrote:
> Ross Paterson writes:
> > I've collected some notes on these issues at
> >
> > http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/StandardClasses
> 
> Coincidentally, I spent some time last week thinking about a replacement
> for the Num class. I think I managed to come up with something that's
> more flexible than Num, but still mostly comprehensible.

The fact that the first part of your structure is much the same as
the one on the web page (which is essentially that part of the revised
numeric prelude plus a Haskell 98-compatible veneer) is evidence that
it's pretty clear what to do with Num and Fractional.

The only point of contention is whether to factor out monoid and
semiring classes.  Arguments against include:

 * There are lots of monoids, and (+) doesn't seem a reasonable symbol
   for some of them.

 * Having (+) work on lists, tuples and all the other monoids would make
   error messages more complicated.

On the other hand, if we had a Natural type, it would be the standard
example of a semiring.

> I'm not sure what the contract is for fromInteger. Perhaps something
> like,
> 
> fromInteger 0 = zero
> fromInteger 1 = one
> fromInteger n | n < 0 = negate (fromInteger (negate n))
> fromInteger n = one + fromInteger (n-1)
> 
> Which, actually, could also be a default definition.

That is also the default definition in the revised numeric prelude,
but we can do better using associativity:

fromInteger n
  | n < 0   =  negate (fi (negate n))
  | otherwise   =  fi n
  where fi 0=  zero
fi 1=  one
fi n
  | even n= fin + fin
  | otherwise = fin + fin + one
  where fin = fi (n `div` 2)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all.

Quoting Henning Thielemann <[EMAIL PROTECTED]>:

> A monoid operation is associative, isn't it?

Duh.  Yes.  Sorry.  Need caffeine.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread David Menendez
Ross Paterson writes:

> Such features would be useful, but are unlikely to be available for
> Haskell'.  If we concede that, is it still desirable to make these
> changes to the class hierarchy?
> 
> I've collected some notes on these issues at
> 
>
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/
StandardClasses

Coincidentally, I spent some time last week thinking about a replacement
for the Num class. I think I managed to come up with something that's
more flexible than Num, but still mostly comprehensible.



> class Monoid a where
>   zero :: a
>   (+) :: a -> a -> a

Laws:
identity : zero + a == a == a + zero
associativity : a + (b + c) == (a + b) + c

Motivation:
Common superclass for Group and Semiring.

> class Monoid a => Group a where
>   negate :: a -> a
>   (-) :: a -> a -> a
> 
>   a - b = a + negate b
>   negate a = zero - a

Laws:
negate (negate a) == a
a + negate a == zero == negate a + a

Motivation:
Money, dimensional quantities, vectors.

An Abelian group is just a group where (+) is commutative. If there's a
need, we can declare a subclass.

For non-Abelian groups, it's important to note that (-) provides right
subtraction.

> class Monoid a => Semiring a where
>   one :: a
>   (*) :: a -> a -> a

Laws:
identity : one * a == a == a * one
associativity : a * (b * c) == (a * b) * c
zero annihilation : zero * a == zero == a * zero

Motivation:
Natural numbers support addition and multiplication, but not
negation.

Unexpectedly, instances of MonadPlus and ArrowPlus can also be
considered Semirings, with (>>) and (>>>) being the multiplication.

Since Semiring is a subclass of Monoid, we get the (+,0) instance for
free. The following wrapper implements the (*,1) monoid.

> newtype Prod a = Prod { unProd :: a }
>
> instance (Semiring a) => Monoid (Prod a) where
>   zero = Prod one
>   Prod a + Prod b = Prod (a * b)

> class (Semiring a, Group a) => Ring a where
>   fromInteger :: Integer -> a

Placing 'fromInteger' here is similar to Num in spirit, but perhaps
undesirable.

I'm not sure what the contract is for fromInteger. Perhaps something
like,

fromInteger 0 = zero
fromInteger 1 = one
fromInteger n | n < 0 = negate (fromInteger (negate n))
fromInteger n = one + fromInteger (n-1)

Which, actually, could also be a default definition.

The original Num class is essentially a Ring with abs, signum, show, and
(==).

> class (Ring a, Eq a, Show a) => Num a where
> abs :: a -> a
> signum :: a -> a

These are probably best put in a NormedRing class or something.



I don't have enough math to judge the classes like Integral, Real,
RealFrac, etc, but Fractional is fairly straightforward.

> class Ring a => DivisionRing a where
>   recip :: a -> a
>   (/) :: a -> a -> a
>   fromRational :: Rational -> a
> 
>   a / b = a * recip b
>   recip a = one / a

Laws:
recip (recip a) == a, unless a == zero
a * recip a == one == recip a * a, unless a == zero

Motivation:
A division ring is essentially a field that doesn't require
multiplication to commute, which allows us to include quaternions and
other non-commuting division algebras.

Again, (/) represents right division.



These show up a lot, but don't have standard classes.

> class (Group g) => GroupAction g a | a -> g where
> add :: g -> a -> a

Laws:
add (a + b) c == add a (add b c)
add zero c == c

Motivation:
Vectors act on points, durations act on times, groups act on
themselves (another wrapper can provide that, if need be).

> class (GroupAction g a) => SymmetricGroupAction g a | a -> g where
> diff :: a -> a -> g

Laws:
diff a b == negate (diff b a)
diff (add a b) b == a

Motivation:
I'm not sure whether this is the correct class name, but it's
certainly a useful operation when applicable.

> class (Ring r, Group a) => Module r a | a -> r where
> mult :: r -> a -> a

Laws:
mult (a * b) c == mult a (mult b c)
mult one c == c

Motivation:
Scalar multiplication is fairly common. A module is essentially a
vector space over a ring, instead of a field.

It's fairly trivial to write an adapter to produce a GroupAction
instance for any Module.



For illustration, here's an example with vectors and points:

> data Pt a = Pt a a deriving (Eq, Show)
> data Vec a = Vec a a deriving (Eq, Show)
> 
> instance (Ring a) => Monoid (Vec a) where
>   zero = Vec 0 0
>   Vec x y + Vec x' y' = Vec (x + x') (y + y')
> 
> instance (Ring a) => Group (Vec a) where
>   Vec x y - Vec x' y' = Vec (x - x') (y - y')
> 
> instance (Ring a) => Module a (Vec a) where
>   mult a (Vec x y) = Vec (a * x) (a * y)
>   
> instance (Ring a) => GroupAction (Vec a) (Pt a) where
>   add (Vec dx dy) (Pt x y) = Pt (dx + x) (dy + y)
> 
> instance (Ring a) => SymmetricGroupAction (Vec a) (Pt a) where
>   diff (Pt x y) (Pt x' y') = Vec (x - x') (y - y')
>
> midpoint p1 p2 = add (mult 0.5 (diff p1 p2)) p

[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Ashley Yakeley

Aaron Denney wrote:


I know of no good way to express that a given data type obeys the
same interface two (or more) ways.


The best approach here is to use data structures instead of classes:

data Monoid a = MkMonoid
{
  monoidNull :: a,
  monoidFunc :: a -> a -> a
}

--
Ashley Yakeley

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Aaron Denney
On 2006-09-13, Ross Paterson <[EMAIL PROTECTED]> wrote:
> On Tue, Sep 12, 2006 at 08:59:30PM -0400, [EMAIL PROTECTED] wrote:
>> One of the proposals that comes up every so often is to allow the
>> declaration of a typeclass instance to automatically declare instances
>> for all superclasses.  So, for example:
>> 
>> class (Functor m) => Monad m where
>> fmap f m = m >>= return . f
>> 
>> instance Monad Foo where
>> return a = {- ... -}
>> m >>= k = {- ... -}
>> fail s = {- ... -}
>> 
>> This will automatically declare an instance of Functor Foo.
>> 
>> Similarly, a finer-grained collection of numeric typeclasses could
>> simply make Num a synonym for (Show a, Ord a, Ring a, Signum a).
>> Declaring an instance for (Num Bar) declares all of the other
>> instances that don't yet have a declaration.
>
> Such features would be useful, but are unlikely to be available for
> Haskell'.  If we concede that, is it still desirable to make these
> changes to the class hierarchy?

Absolutely.  It needs to be fixed, and much better now than later.

-- 
Aaron Denney
-><-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Jacques Carette
Your solution would imply[1] that all Rational are multiplicatively 
invertible -- which they are not.


The Rationals are not a multiplicative group -- although the _positive_ 
Rationals are.  You can't express this in Haskell's type system AFAIK.


Your basic point is correct: if you are willing to use a tag (like 
Multiply and Add), then you can indeed have a domain be seen as matching 
an interface in 2 different ways.  Obviously, this can be extended to n 
different ways with appropriate interfaces. 


Jacques

[1] imply in the sense of intensional semantics, since we all know that 
Haskell's type system is not powerful enough to enforce axioms.


PS: if you stick to 2 Monoidal structures, you'll be on safer grounds.

Brian Hulley wrote:
If the above is equivalent to saying "Monoid is a *superclass* of 
SemiRing in two different ways", then can someone explain why this 
approach would not work (posted earlier):


   data Multiply = Multiply
   data Add = Add

   class Group c e where
   group :: c -> e -> e -> e
   identity :: c -> e
   inverse :: c -> e -> e

   instance Group Multiply Rational where
   group Multiply x y = ...
   identity Multiply = 1
   inverse Multiply x = ...

   instance Group Add Rational where
   group Add x y = ...
   identity Add = 0
   inverse Add x = ...

   (+) :: Group Add a => a -> a -> a
   (+) = group Add

   (*) = group Multiply

   class (Group Multiply a, Group Add a) => Field a where ...

If the objection is just that you can't make something a subclass in 
two different ways, the above is surely a counterexample. Of course I 
made the above example more fixed than it should be ie:


   class (Group mult a, Group add a) => Field mult add a where ...

and only considered the relationship between groups and fields - 
obviously other classes would be needed before and in-between, but 
perhaps the problem is that even with extra parameters (to represent 
*all* the parameters in the corresponding tuples used in maths), there 
is no way to get a hierarchy?


Thanks, Brian.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Brian Hulley

Henning Thielemann wrote:

On Wed, 13 Sep 2006, Lennart Augustsson wrote:

I don't think Haskell really has the mechanisms for setting up an
algebraic class hierarchy the right way.  Consider some classes we
might want to build: SemiGroup
Monoid
AbelianMonoid
Group
AbelianGroup
SemiRing
Ring
...

The problem is that going from, say, AbelianMonoid to SemiRing you
want to add a new Monoid (the multiplicative) to the class.  So
SemiRing is a subclass of Monoid in two different way, both for +
and for *.
I don't know of any nice way to express this is Haskell.


Thanks for confirming what I wrote. :-)


If the above is equivalent to saying "Monoid is a *superclass* of SemiRing 
in two different ways", then can someone explain why this approach would not 
work (posted earlier):


   data Multiply = Multiply
   data Add = Add

   class Group c e where
   group :: c -> e -> e -> e
   identity :: c -> e
   inverse :: c -> e -> e

   instance Group Multiply Rational where
   group Multiply x y = ...
   identity Multiply = 1
   inverse Multiply x = ...

   instance Group Add Rational where
   group Add x y = ...
   identity Add = 0
   inverse Add x = ...

   (+) :: Group Add a => a -> a -> a
   (+) = group Add

   (*) = group Multiply

   class (Group Multiply a, Group Add a) => Field a where ...

If the objection is just that you can't make something a subclass in two 
different ways, the above is surely a counterexample. Of course I made the 
above example more fixed than it should be ie:


   class (Group mult a, Group add a) => Field mult add a where ...

and only considered the relationship between groups and fields - obviously 
other classes would be needed before and in-between, but perhaps the problem 
is that even with extra parameters (to represent *all* the parameters in the 
corresponding tuples used in maths), there is no way to get a hierarchy?


Thanks, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Henning Thielemann

On Wed, 13 Sep 2006 [EMAIL PROTECTED] wrote:

> G'day all.
> 
> Quoting Henning Thielemann <[EMAIL PROTECTED]>:
> 
> > ... which got the same name, too, namely 'foldl'.
> 
> You mean foldr.  The place of foldl is a bit tricky, but in this case
> it requires that the monoid be Abelian.

A monoid operation is associative, isn't it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all.

Quoting Henning Thielemann <[EMAIL PROTECTED]>:

> ... which got the same name, too, namely 'foldl'.

You mean foldr.  The place of foldl is a bit tricky, but in this case
it requires that the monoid be Abelian.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Henning Thielemann

On Wed, 13 Sep 2006, Lennart Augustsson wrote:

> The sum function really only needs the argument list to be a monoid.
> And the same is true for the product function, but with 1 and * as the monoid
> operators.  Sum and product are really the same function. :)

... which got the same name, too, namely 'foldl'. 'sum' and 'product'
derive the operation and the neutral element from the operand types,
'foldl' expect them explicitly.

> I don't think Haskell really has the mechanisms for setting up an algebraic
> class hierarchy the right way.  Consider some classes we might want to build:
> SemiGroup
> Monoid
> AbelianMonoid
> Group
> AbelianGroup
> SemiRing
> Ring
> ...
> 
> The problem is that going from, say, AbelianMonoid to SemiRing you want to add
> a new Monoid (the multiplicative) to the class.  So SemiRing is a subclass of
> Monoid in two different way, both for + and for *.
> I don't know of any nice way to express this is Haskell.

Thanks for confirming what I wrote. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Lennart Augustsson

The sum function really only needs the argument list to be a monoid.
And the same is true for the product function, but with 1 and * as  
the monoid operators.  Sum and product are really the same function. :)


I don't think Haskell really has the mechanisms for setting up an  
algebraic class hierarchy the right way.  Consider some classes we  
might want to build:

SemiGroup
Monoid
AbelianMonoid
Group
AbelianGroup
SemiRing
Ring
...

The problem is that going from, say, AbelianMonoid to SemiRing you  
want to add a new Monoid (the multiplicative) to the class.  So  
SemiRing is a subclass of Monoid in two different way, both for + and  
for *.

I don't know of any nice way to express this is Haskell.

-- Lennart

On Sep 13, 2006, at 03:26 , [EMAIL PROTECTED] wrote:


G'day all.

Quoting Jason Dagit <[EMAIL PROTECTED]>:


I was making an embedded domain specific language for excel
spreadsheet formulas recently and found that making my formula
datatype an instance of Num had huge pay offs.


Just so you know, what we're talking about here is a way to make that
even _more_ useful by dicing up Num.


I can even use things like Prelude.sum to
add up cells.


Ah, but the sum function only needs 0 and (+), so it doesn't need
the full power of Num.  It'd be even _more_ useful if it worked on
all data types which supported 0 and (+), but not necessarily (*):

sum :: (AdditiveAbelianMonoid a) => [a] -> a

product :: (MultiplicativeAbelianMonoid a) => [a] -> a

Those are bad typeclass names, but you get the idea.

Right now, to reuse sum, people have to come up with fake
implementations for Num operations that simply don't make sense on
their data type, like signum on Complex numbers.


 All I really needed was to define Show and Num
correctly,  neither of which took much mental effort or coding  
tricks.


You also needed to derive Eq, which gives you, in your case,  
structural
equality rather than semantic equality (which is probably  
undecidable for

your DSL).

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Henning Thielemann

On Tue, 12 Sep 2006, Aaron Denney wrote:

> On 2006-09-12, Bryan Burgers <[EMAIL PROTECTED]> wrote:
> > And another problem I can see is that, for example, the Integers are a
> > group over addition, and also a group over multiplication;
> 
> Not over multiplication, no, because there is no inverse.
> 
> I know of no good way to express that a given data type obeys the
> same interface two (or more) ways.  Some OO languages try to handle the
> case of of an abstract base class being inherited twice through two
> different intermediate classes, but none of them do it well.

Some examples are:
  Cardinals are a lattice with respect to (min,max) and (gcd,lcm)
  Sequences are rings if the multiplication is defined as
1) element-wise multiplication
2) convolution

We could certainly go a similar way and define newtypes in order to
provide different sets of operations for the same data structure.

 One issue is, that we have some traditional arithmetical signs and want
to use them in the traditional way. But there is no simple correspondence
between signs and laws. Both "+" and "*" fulfill monoid or group laws
depending on the type. If we had a sign for "group operation", say "." we
had to write "'.' of the additive group of rationals" instead of "+" and
"'.' of the multiplicative group of rationals" instead of "*". I don't
know how to handle this in a programming language.
 We also know that floating point numbers violate most basic laws. But
also wrappers to other languages violate basic laws. E.g. if the Haskell
expression (a+b) is mapped to an expression of a foreign language, say
(add a b), then (b+a) will be mapped to (add b a). That is, this instance
of Haskell's (+) is not commutative.
 The mathematical concept of calling a tuple of a set of objects and some
operations a group, a ring or whatever is not exactly mapped to Haskell's
type classes. It is even used laxly in mathematics. One often says "the
set of integers is a ring".
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread Ross Paterson
On Tue, Sep 12, 2006 at 08:59:30PM -0400, [EMAIL PROTECTED] wrote:
> One of the proposals that comes up every so often is to allow the
> declaration of a typeclass instance to automatically declare instances
> for all superclasses.  So, for example:
> 
> class (Functor m) => Monad m where
> fmap f m = m >>= return . f
> 
> instance Monad Foo where
> return a = {- ... -}
> m >>= k = {- ... -}
> fail s = {- ... -}
> 
> This will automatically declare an instance of Functor Foo.
> 
> Similarly, a finer-grained collection of numeric typeclasses could
> simply make Num a synonym for (Show a, Ord a, Ring a, Signum a).
> Declaring an instance for (Num Bar) declares all of the other
> instances that don't yet have a declaration.

Such features would be useful, but are unlikely to be available for
Haskell'.  If we concede that, is it still desirable to make these
changes to the class hierarchy?

I've collected some notes on these issues at

http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/StandardClasses

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all.

Quoting Jason Dagit <[EMAIL PROTECTED]>:

> I was making an embedded domain specific language for excel
> spreadsheet formulas recently and found that making my formula
> datatype an instance of Num had huge pay offs.

Just so you know, what we're talking about here is a way to make that
even _more_ useful by dicing up Num.

> I can even use things like Prelude.sum to
> add up cells.

Ah, but the sum function only needs 0 and (+), so it doesn't need
the full power of Num.  It'd be even _more_ useful if it worked on
all data types which supported 0 and (+), but not necessarily (*):

sum :: (AdditiveAbelianMonoid a) => [a] -> a

product :: (MultiplicativeAbelianMonoid a) => [a] -> a

Those are bad typeclass names, but you get the idea.

Right now, to reuse sum, people have to come up with fake
implementations for Num operations that simply don't make sense on
their data type, like signum on Complex numbers.

>  All I really needed was to define Show and Num
> correctly,  neither of which took much mental effort or coding tricks.

You also needed to derive Eq, which gives you, in your case, structural
equality rather than semantic equality (which is probably undecidable for
your DSL).

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Jason Dagit

On 9/12/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:

G'day all.

Quoting Henning Thielemann <[EMAIL PROTECTED]>:

> More precisely: Can you tell me the difference between numbers and "more
> complex mathematical objects"?

Yes.  A Num is anything which supports the common mathematically-
significant operations which are supported by the basic built-in machine
types such as Int and Double.  It need not _be_ a built-in machine type,
but it must support those operations.


And as an example of something which is useful as an instance of num
but isn't a number I have a recent experience I can share.

I was making an embedded domain specific language for excel
spreadsheet formulas recently and found that making my formula
datatype an instance of Num had huge pay offs.  You write formulas in
haskell code and then to turn them into something excel can chew on
you only need to show them.  I can even use things like Prelude.sum to
add up cells.  All I really needed was to define Show and Num
correctly,  neither of which took much mental effort or coding tricks.
Now I get tons for free.

Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread ajb
G'day all.

Quoting Henning Thielemann <[EMAIL PROTECTED]>:

> It seems we are at a point, where we have to define what is a 'number'.

For backwards compatibility, I'd say a Num is what it is at the
moment.

One of the proposals that comes up every so often is to allow the
declaration of a typeclass instance to automatically declare instances
for all superclasses.  So, for example:

class (Functor m) => Monad m where
fmap f m = m >>= return . f

instance Monad Foo where
return a = {- ... -}
m >>= k = {- ... -}
fail s = {- ... -}

This will automatically declare an instance of Functor Foo.

Similarly, a finer-grained collection of numeric typeclasses could
simply make Num a synonym for (Show a, Ord a, Ring a, Signum a).
Declaring an instance for (Num Bar) declares all of the other
instances that don't yet have a declaration.

> More precisely: Can you tell me the difference between numbers and "more
> complex mathematical objects"?

Yes.  A Num is anything which supports the common mathematically-
significant operations which are supported by the basic built-in machine
types such as Int and Double.  It need not _be_ a built-in machine type,
but it must support those operations.

(Yes, some architectures support vector operations.  This doesn't count
as "basic".  No, some architectures don't support Double or Word64
natively.  I don't care.)

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Brian Hulley

Bryan Burgers wrote:

That being said, I'll have to play the other side of the coin: it
would probably be a little bit of a pain to have to define instances
of each data declaration (Integer, Int, Float, Matrix, Complex, etc.)
on each of these seperate classes--especially when being in a certain
class usually implies being in another (ie, the definition of a set
being a field requires that that set is a group, right?)


Aaron Denney wrote:

On 2006-09-12, Bryan Burgers <[EMAIL PROTECTED]> wrote:

And another problem I can see is that, for example, the Integers are
a group over addition, and also a group over multiplication;


Not over multiplication, no, because there is no inverse.

I know of no good way to express that a given data type obeys the
same interface two (or more) ways.  Some OO languages try to handle
the case of of an abstract base class being inherited twice through
two different intermediate classes, but none of them do it well.


How about:

   data Multiply = Multiply
   data Add = Add

   class Group c e where
   group :: c -> e -> e -> e
   identity :: c -> e
   inverse :: c -> e -> e

   instance Group Multiply Rational where
   group Multiply x y = ...
   identity Multiply = 1
   inverse Multiply x = ...

   instance Group Add Rational where
   group Add x y = ...
   identity Add = 0
   inverse Add x = ...

   (+) :: Group Add a => a -> a -> a
   (+) = group Add

   (*) = group Multiply

   class (Group Multiply a, Group Add a) => Field a where ...

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Jacques Carette

First, as already pointed out in
http://www.haskell.org/pipermail/haskell-cafe/2006-April/015404.html
there is a lot of relevant previous work in this area.

Aaron Denney wrote:

I know of no good way to express that a given data type obeys the
same interface two (or more) ways.  Some OO languages try to handle the
case of of an abstract base class being inherited twice through two
different intermediate classes, but none of them do it well.
  
This is very easy to do in 'raw' category theory, as concepts are not 
_nominal_, so a functor from one type to another can explicitly do a 
renaming if necessary.  Various algebraic specification languages have 
thus adopted this too, so that you are not forced to give unique names 
to all your concepts, you can in fact give them meaningful names 'in 
context', and use a remapping when you want to say that you obey a 
particular interface.


This is an old conversation, see
http://www.haskell.org/pipermail/haskell/2005-October/016621.html
for example.

Jacques
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Aaron Denney
On 2006-09-12, Bryan Burgers <[EMAIL PROTECTED]> wrote:
> And another problem I can see is that, for example, the Integers are a
> group over addition, and also a group over multiplication;

Not over multiplication, no, because there is no inverse.

I know of no good way to express that a given data type obeys the
same interface two (or more) ways.  Some OO languages try to handle the
case of of an abstract base class being inherited twice through two
different intermediate classes, but none of them do it well.

-- 
Aaron Denney
-><-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Tim Walkenhorst

Bryan Burgers schrieb:

[...] it would probably be a little bit of a pain to have to define 
instances

of each data declaration (Integer, Int, Float, Matrix, Complex, etc.)
on each of these seperate classes--especially when being in a certain
class usually implies being in another [...]


Something like John Meacham's class alias proposal might help here:
http://repetae.net/john/recent/out/classalias.html


Tim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Bryan Burgers

It seems we are at a point, where we have to define what is a 'number'.
More precisely: Can you tell me the difference between numbers and "more
complex mathematical objects"? Is a complex number a number? Is a
quaternion a number? Is a residue class a number? We can calculate with
integers modulo some other integer like with integers - is that considered
computation with numbers? Shall we distinguish between matrices of numbers
and matrices of more complex mathematical objects? In signal theory
matrices of polynomials are very common.


My question would be why is it so important to determine what is or
isn't a number? Whether something is a number or not does not
determine what operations and properties it has. Rather, we should try
to determine what is a field, a ring, a group, etc. If we know that
matrices of polynomials form a group, then we can perform the
operations of the group on those objects.

That being said, I'll have to play the other side of the coin: it
would probably be a little bit of a pain to have to define instances
of each data declaration (Integer, Int, Float, Matrix, Complex, etc.)
on each of these seperate classes--especially when being in a certain
class usually implies being in another (ie, the definition of a set
being a field requires that that set is a group, right?) And another
problem I can see is that, for example, the Integers are a group over
addition, and also a group over multiplication; and in my small bit of
thinking about this, it seems that having to keep track of all of this
might get a bit unruly.

Bryan Burgers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread Henning Thielemann

On Mon, 11 Sep 2006, Ross Paterson wrote:

> On Mon, Sep 11, 2006 at 04:26:30PM +0200, Henning Thielemann wrote:
> > On Sat, 9 Sep 2006, Ross Paterson wrote:
> > > I think that a finer grain numeric hierarchy, while retaining Num, etc,
> > > is feasible without changing the language: unlike the case of monads,
> > > the people who will be defining instances of numeric classes are the
> > > very ones who are inconvenienced by the current hierarchy.  The main
> > > impact on clients of the classes is that some functions would have
> > > more general types.
> > 
> > There are many Num instances around in libraries where people wrap to
> > external libraries: functionalMetapost, CSound wrapper in Haskore,
> > SuperCollider (GSL too?). What about Num (algebraically Ring) instances of
> > polynomials, residue classes and other such advanced mathematical objects?
> 
> And what do abs and signum mean for Haskore's orchestra expressions,
> polynomials, residue classes, vectors, matrices, functions, etc?

For clarification: Haskore does not define any arithmetic for music, but
CSound provides some arithmetic and Haskell wraps it with Num instances.

> The people who define those wish they were defining Ring, but they must
> define Num.

It seems we are at a point, where we have to define what is a 'number'.  
More precisely: Can you tell me the difference between numbers and "more
complex mathematical objects"? Is a complex number a number? Is a
quaternion a number? Is a residue class a number? We can calculate with
integers modulo some other integer like with integers - is that considered
computation with numbers? Shall we distinguish between matrices of numbers
and matrices of more complex mathematical objects? In signal theory
matrices of polynomials are very common.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes (Was: map (-2) [1..5])

2006-09-11 Thread Aaron Denney
On 2006-09-11, Henning Thielemann <[EMAIL PROTECTED]> wrote:
>
> On Sat, 9 Sep 2006, Ross Paterson wrote:
>
>> On Sat, Sep 09, 2006 at 12:57:56AM -0400, Cale Gibbard wrote:
>> > Num itself needs to be split, but we can't do it sanely without
>> > something like class aliases.
>> 
>> I think that a finer grain numeric hierarchy, while retaining Num, etc,
>> is feasible without changing the language: unlike the case of monads,
>> the people who will be defining instances of numeric classes are the
>> very ones who are inconvenienced by the current hierarchy.  The main
>> impact on clients of the classes is that some functions would have
>> more general types.
>
> There are many Num instances around in libraries where people wrap to
> external libraries: functionalMetapost, CSound wrapper in Haskore,
> SuperCollider (GSL too?). What about Num (algebraically Ring) instances of
> polynomials, residue classes and other such advanced mathematical objects?

Yes, they would need to move definitions around.  I think it'd be worth
it for Haskell'.

-- 
Aaron Denney
-><-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Numeric type classes (Was: map (-2) [1..5])

2006-09-11 Thread Ross Paterson
On Mon, Sep 11, 2006 at 04:26:30PM +0200, Henning Thielemann wrote:
> On Sat, 9 Sep 2006, Ross Paterson wrote:
> > I think that a finer grain numeric hierarchy, while retaining Num, etc,
> > is feasible without changing the language: unlike the case of monads,
> > the people who will be defining instances of numeric classes are the
> > very ones who are inconvenienced by the current hierarchy.  The main
> > impact on clients of the classes is that some functions would have
> > more general types.
>
> There are many Num instances around in libraries where people wrap to
> external libraries: functionalMetapost, CSound wrapper in Haskore,
> SuperCollider (GSL too?). What about Num (algebraically Ring) instances of
> polynomials, residue classes and other such advanced mathematical objects?

And what do abs and signum mean for Haskore's orchestra expressions,
polynomials, residue classes, vectors, matrices, functions, etc?
The people who define those wish they were defining Ring, but they
must define Num.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe