Deja vu: Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Laszlo Nemeth


[incomprehensible (not necessarily wrong!) stuff about polynomials,
 rings, modules over Z and complaints about the current prelude nuked]

--- Marcin 'Qrczak' Kowalczyk pisze ---

> Please show a concrete proposal how Prelude classes could be improved.

--- Jerzy Karczmarczuk repondre ---

> I am Haskell USER. I have no ambition to save the world. The "proposal"
> has been presented in 1995 in Nijmegen (FP in education). Actually, it
> hasn't, I concentrated on lazy power series etc., and the math oriented
> prelude has been mentioned casually. Jeroen Fokker presented similar
> ideas, implemented differently. 

I'm afraid all this discussion reminds me the one we had a year or two
ago. At that time the mathematically inclined side was lead by Sergei,
who to his credit developed the Basic Algebra Proposal, which I don't
understand, but many people seemed to be happy about at that time. And
then of course nothing happend, because no haskell implementor has
bitten the bullet and implemented the proposal. This is something
understandable as supporting Sergei's proposal seem to be a lot of
work, most of which would be incompatible with current
implementations. And noone wants to maintain *two* haskell compilers
within one.

Even if this discussion continues and another brave soul develops
another algebra proposal I am prepared to bet with both of you in one
years supply of Ben and Jerry's (not Jerzy :)!) icecream that nothing
will continue to happen on the implementors side. It is simply too
much work for an *untested* (in practice, for teaching etc)
alternative prelude.

So instead of wasting time, why don't you guys ask the implementors to
provide a flag '-IDontWantYourStinkingPrelude' which would give you a
bare metal compiler with no predefined types, functions, classes, no
derived instances, no fancy stuff and build and test your proposals
with it?

I guess the RULES pragma (in GHC) could be abused to allow access to
the primitive operations (on Ints), but you are still likely to loose
much of the elegance, conciseness and perhaps even some efficiency of
Haskell (e.g. list comprehensions), but this should allow us to gain
experience in what sort of support is essential for providing
alternative prelude(s). Once we learnt how to decouple the prelude
from the compiler, and gained experience with alternative preludes
implementors would have no excuse not to provide the possibility
(unless it turns out to be completely impossible or impractical, in
which case we learnt something genuinely useful).

So, Marcin (as you are one of the GHC implementors), how much work
would it be do disable the disputed Prelude stuff within the compiler,
and what would be lost?

Laszlo

[Disclaimer: Just my 10 wons. This message is not in disagreement or
 agreement with any of the previous messages]

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Joe Fasel


On 12-Feb-2001 William Lee Irwin III wrote:
| On Mon, Feb 12, 2001 at 02:13:38PM -0700, Joe Fasel wrote:
|> signum does make sense.  You want abs and signum to obey these laws:
|> 
|> x == abs x * signum x
|> abs (signum x) == (if abs x == 0 then 0 else 1)
|> 
|> Thus, having fixed an appropriate matrix norm, signum is a normalization
|> function, just as with reals and complexes.
| 
| This works fine for matrices of reals, for matrices of integers and
| polynomials over integers and the like, it breaks down quite quickly.
| It's unclear that in domains like that, the norm would be meaningful
| (in the sense of something we might want to compute) or that it would
| have a type that meshes well with a class hierarchy we might want to
| design. Matrices over Z/nZ for various n and Galois fields, and perhaps
| various other unordered algebraically incomplete rings explode this
| further still.

Fair enough.  So, the real question is not whether signum makes sense,
but whether abs does.  I guess the answer is that it does for matrix rings
over division rings.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Technology Modeling and Analysisphone: +1 505 667 7158
University of Californiafax:   +1 505 667 2960
Los Alamos National Laboratory  post:  TSA-7 MS F609; Los Alamos, NM 87545

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread William Lee Irwin III

On Mon, Feb 12, 2001 at 02:13:38PM -0700, Joe Fasel wrote:
> For fromInteger, fromInt, and abs, the result should be a scalar matrix.
> For the two coercions, I don't think there would be much controversy
> about this. I agree that it would be nice if abs could return a
> scalar, but this requires multiparameter classes, so we have to make
> do with a scalar matrix.

I'm not a big fan of this approach. I'd like to see at least some
attempt to statically type dimensionality going on, and that flies in
the face of it. Worse yet, coercing integers to matrices is likely to
be a programmer error.

On Mon, Feb 12, 2001 at 02:13:38PM -0700, Joe Fasel wrote:
> signum does make sense.  You want abs and signum to obey these laws:
> 
> x == abs x * signum x
> abs (signum x) == (if abs x == 0 then 0 else 1)
> 
> Thus, having fixed an appropriate matrix norm, signum is a normalization
> function, just as with reals and complexes.

This works fine for matrices of reals, for matrices of integers and
polynomials over integers and the like, it breaks down quite quickly.
It's unclear that in domains like that, the norm would be meaningful
(in the sense of something we might want to compute) or that it would
have a type that meshes well with a class hierarchy we might want to
design. Matrices over Z/nZ for various n and Galois fields, and perhaps
various other unordered algebraically incomplete rings explode this
further still.

On Mon, Feb 12, 2001 at 02:13:38PM -0700, Joe Fasel wrote:
> If we make the leap to multiparameter classes, I think this is
> the signature we want:

Well, nothing is going to satisfy everyone. It's pretty reasonable,
though.

Cheers,
Bill

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Joe Fasel


On 09-Feb-2001 William Lee Irwin III wrote:
| Matrix rings actually manage to expose the inappropriateness of signum
| and abs' definitions and relationships to Num very well:
| 
| class  (Eq a, Show a) => Num a  where
| (+), (-), (*)   :: a -> a -> a
| negate  :: a -> a
| abs, signum :: a -> a
| fromInteger :: Integer -> a
| fromInt :: Int -> a -- partain: Glasgow extension
| 
| Pure arithmetic ((+), (-), (*), negate) works just fine.
| 
| But there are no good injections to use for fromInteger or fromInt,
| the type of abs is wrong if it's going to be a norm, and it's not
| clear that signum makes much sense.

For fromInteger, fromInt, and abs, the result should be a scalar matrix.
For the two coercions, I don't think there would be much controversy about this.
I agree that it would be nice if abs could return a scalar, but this requires
multiparameter classes, so we have to make do with a scalar matrix.

We already have this problem with complex numbers:  It might be nice
if the result of abs were real.

signum does make sense.  You want abs and signum to obey these laws:

x == abs x * signum x
abs (signum x) == (if abs x == 0 then 0 else 1)

Thus, having fixed an appropriate matrix norm, signum is a normalization
function, just as with reals and complexes.

If we make the leap to multiparameter classes, I think this is
the signature we want:

class (Eq a, Show a) => Num a b | a --> b where
(+), (-), (*)   :: a -> a -> a
negate  :: a -> a
abs :: a -> b
signum  :: a -> a
scale   :: b -> a -> a
fromInteger :: Integer -> a
fromInt :: Int -> a

Here, b is the type of norms of a.  Instead of the first law above, we have

x == scale (abs x) (signum x)

All this, of course, is independent of whether we want a more proper
algebraic class hierarchy, with (+) introduced by Monoid, negate and (-)
by Group, etc.

Cheers,
--Joe

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Technology Modeling and Analysisphone: +1 505 667 7158
University of Californiafax:   +1 505 667 2960
Los Alamos National Laboratory  post:  TSA-7 MS F609; Los Alamos, NM 87545

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Jerzy Karczmarczuk

Marcin Kowalczyk continues:

> On Mon, 12 Feb 2001, Jerzy Karczmarczuk wrote:
> 
> > I want to be *able* to define mathematical operations upon objects
> > which by their intrinsic nature permit so!
> 
> You can't do it in Haskell as it stands now, no matter what the Prelude
> would be.
> 
> For example I would say that with the definition
> abs x = if x >= 0 then x else -x
> it's obvious how to obtain abs :: ([Int]->Int) -> ([Int]->Int): apply the
> definition pointwise.
> 
> But it will never work in Haskell, unless we changed the type rules for if
> and the tyoe of the result of (>=).
> 
> You are asking for letting
> abs x = max x (-x)
> work on functions. OK, in this particular case it can be made to work 
 

Why don't you try from time to time to attempt to understand what
other people want? And wait, say 2 hours, before responding? 

I DON'T WANT max TO WORK ON FUNCTIONS. I never did. I will soon (because
I am writing a graphical package where max serves to intersect implicit
graphical objects) need that, but for very specific functions which
represent textures, but NOT in general.

I repeat for the last time, that I want to have those operations which
are *implied* by the mathematical properties. And anyway, if you replace
x>=0 by x>=zero with an appropriate zero, this should work as well.
I want only that Prelude avoids spurious dependencies.

This is the way I program in Clean, where there is no Num, and (+), (*),
zero, abs, etc. constitute classes by themselves. So, when you say:

> You are asking for an impossible thing.

My impression is what is impossible, is your way of interpreting/
understanding the statements (and/or desiderata) of other people. 

> > I defined hundred times some special functions to add lists or
> > records, to multiply a tree by a scalar (btw.: Jón Fairbarn proposes
> > (.*), I have in principle nothing against, but these operators is used
> > elsewhere, in other languages, CAML and Matlab; I use (*>) ).
> 
> Please show a concrete proposal how Prelude classes could be improved.

(Why do you precede your query by this citation? What do you have to say
here about the syntax proposed by Jón Fairbarn, or whatever??)

I am Haskell USER. I have no ambition to save the world. The "proposal"
has been presented in 1995 in Nijmegen (FP in education). Actually, it
hasn't, I concentrated on lazy power series etc., and the math oriented
prelude has been mentioned casually. Jeroen Fokker presented similar
ideas, implemented differently. 
If you have nothing else to do (but only in this case!) you may find 
the modified prelude called math.hs for Hugs (which needs a modified 
prelude.hs exporting primitives) in 

http://users.info.unicaen.fr/~karczma/humat/

This is NOT a "public proposal" and I *don't want* your public comments
on it. If you want to be nice, show me some of *your* Haskell programs.

Jerzy Karczmarczuk
Caen, France

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Marcin 'Qrczak' Kowalczyk

On Mon, 12 Feb 2001, Jerzy Karczmarczuk wrote:

> I want to be *able* to define mathematical operations upon objects
> which by their intrinsic nature permit so!

You can't do it in Haskell as it stands now, no matter what the Prelude
would be.

For example I would say that with the definition
abs x = if x >= 0 then x else -x
it's obvious how to obtain abs :: ([Int]->Int) -> ([Int]->Int): apply the
definition pointwise.

But it will never work in Haskell, unless we changed the type rules for if
and the tyoe of the result of (>=).

You are asking for letting
abs x = max x (-x)
work on functions. OK, in this particular case it can be made to work by
making appropriate instances, but it's because this is a special case
where all intermediate types are appropriately polymorphic.

This technique cannot work in general, as the previous example shows. So
IMHO it's better to not try to pretend that functions can be implicitly
lifted. Better provide as convenient as possible way of manual lifting
arbitrary functions, so it doesn't matter if they have fixed Integer in
the result or not.

You are asking for an impossible thing.

> I defined hundred times some special functions to add lists or
> records, to multiply a tree by a scalar (btw.: Jón Fairbarn proposes
> (.*), I have in principle nothing against, but these operators is used
> elsewhere, in other languages, CAML and Matlab; I use (*>) ).

Please show a concrete proposal how Prelude classes could be improved.

-- 
Marcin 'Qrczak' Kowalczyk


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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Jerzy Karczmarczuk

Marcin Kowalczyk wrote:
> 
> Jerzy Karczmarczuk wrote:
> 
> > I not only feel the need, but I feel that this is important that the
> > additive structure in the codomain is inherited by functions.
> 
> It could support only the basic arithmetic. It would not automatically
> lift an expression which uses (>) and if. It would be inconsistent to
> provide a shortcut for a specific case, where generally it must be
> explicitly lifted anyway. Note that it does make sense to lift (>) and if,
> only the type system does not permit it implicitly because a type is fixed
> to Bool.
> 
> Lifting is so easy to do manually that I would definitely not constrain
> the whole Prelude class system only to have convenient lifting of basic
> arithmetic. When it happens that an instance of an otherwise sane class
> for functions makes sense, then OK, but nothing more.

Sorry for quoting in extenso the full posting just to say:

I haven't the slightest idea what are you talking about.

-- but I want to avoid partial quotations and misunderstandings
resulting
thereof. I don't want any automatic lifting nor *constrain* the Prelude
class. I want to be *able* to define mathematical operations upon
objects
which by their intrinsic nature permit so!

My goodness, I suspect really that despite plenty of opinions you
express
every day on this list you didn't really try to program something in 
HaskellIN A MATHEMATICALLY NON-TRIVIAL CONTEXT.

I defined hundred times some special functions to add lists or records,
to multiply a tree by a scalar (btw.: Jón Fairbarn proposes (.*), I have
in principle nothing against, but these operators is used elsewhere, in
other languages, CAML and Matlab; I use (*>) ).

I am fed up with solutions ad hoc, knowing that correct mathematical
hierarchies permit to inherit plenty of subsumptions, e.g. the fact that
x+x exists implies 2*x.

Thank you for reminding me that manual lifting is easy. 
In fact, everything is easy. Type-checking as well. Let's go back to
assembler.

Jerzy Karczmarczuk

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Marcin 'Qrczak' Kowalczyk

On Mon, 12 Feb 2001, Jerzy Karczmarczuk wrote:

> I not only feel the need, but I feel that this is important that the
> additive structure in the codomain is inherited by functions.

It could support only the basic arithmetic. It would not automatically
lift an expression which uses (>) and if. It would be inconsistent to
provide a shortcut for a specific case, where generally it must be
explicitly lifted anyway. Note that it does make sense to lift (>) and if,
only the type system does not permit it implicitly because a type is fixed
to Bool.

Lifting is so easy to do manually that I would definitely not constrain
the whole Prelude class system only to have convenient lifting of basic
arithmetic. When it happens that an instance of an otherwise sane class
for functions makes sense, then OK, but nothing more.

-- 
Marcin 'Qrczak' Kowalczyk


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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread William Lee Irwin III

In a later posting Marcin Kowalczyk says:
>> If (+) can be implicitly lifted to functions, then why not signum?
>> Note that I would lift neither signum nor (+). I don't feel the need.
>>  ...

On Mon, Feb 12, 2001 at 09:33:03AM +, Jerzy Karczmarczuk wrote:
> I not only feel the need, but I feel that this is important that the
> additive structure in the codomain is inherited by functions. In a more
> specific context: the fact that linear functionals over a vector space
> form also a vector space, is simply *fundamental* for the quantum 
> mechanics, for the cristallography, etc. You don't need to be a Royal
> Abstractor to see this. 

I see this in a somewhat different light, though I'm in general agreement.

What I'd like to do is to be able to effectively model module structures
in the type system, and furthermore be able to simultaneously impose
distinct module structures on a particular type. For instance, complex
n-vectors are simultaneously C-modules and R-modules. and an arbitrary
commutative ring R is at once a Z-module and an R-module. Linear
functionals, which seem like common beasts (try a partially applied
inner product) live in the mathematical structure Hom_R(M,R) which is once
again an R-module, and, perhaps, by inheriting structure on R, an R'
module from various R'. So how does this affect Prelude design? Examining
a small bit of code could be helpful:

-- The group must be Abelian. I suppose anyone could think of this.
class (AdditiveGroup g, Ring r) => LeftModule g r where
(&) :: r -> g -> g

instance AdditiveGroup g => LeftModule g Integer where
n & x   | n == 0 = one
| n < 0  = -(n & (-x))
| n > 0  = x + (n-1) & x

... and we naturally acquire the sort of structure we're looking for.
But this only shows a possible outcome, and doesn't motivate the
implementation. What _will_ motivate the implementation is the sort
of impact this has on various sorts of code:

(1) The fact that R is an AdditiveGroup immediately makes it a
Z-module, so we have mixed-mode arithmetic by a different
means from the usual implicit coercion.

(2) This sort of business handles vectors quite handily.

(3) The following tidbit of code immediately handles curried innerprods:

instance (AdditiveGroup group, Ring ring) => LeftModule (group->ring) ring
where
r & g = \g' -> r & g g'

(4) Why would we want to curry innerprods? I envision:

type SurfaceAPoles foo = SomeGraph (SomeVector foo)

and then

surface :: SurfaceAPoles bar
innerprod v `fmap` normalsOf faces where faces = facesOf surface

(5) Why would we want to do arithmetic on these beasts now that
we think we might need them at all?

If we're doing things like determining the light reflected off of the
various surfaces we will want to scale and add together the various
beasties. Deferring the innerprod operation so we can do this is inelegant
and perhaps inflexible compared to:

lightSources :: [(SomeVector foo -> Intensity foo, Position)]
lightSources = getLightSources boundingSomething
reflection = sum $ map (\(f,p) -> getSourceWeight p * f) lightSources
reflection `fmap` normalsOf faces where faces = facesOf surface

and now in the lightSources perhaps ambient light can be represented
very conveniently, or at least the function type serves to abstract out
the manner in which the orientation of a surface determines the amount
of light reflected off it.

(My apologies for whatever inaccuracies are happening with the optics
here, it's quite far removed from my direct experience.)

Furthermore, within things like small interpreters, it is perhaps
convenient to represent the semantic values of various expressions by
function types. If one should care to define arithmetic on vectors and
vector functions in the interpreted language, support in the source
language allows a more direct approach. This would arise within solid
modelling and graphics once again, as little languages are often used
to describe objects, images, and the like.

How can we anticipate all the possible usages of pretty-looking vector
and matrix algebra? I suspect graphics isn't the only place where
linear algebra could arise. All sorts of differential equation models
of physical phenomena, Markov models of state transition systems, even
economic models at some point require linear algebra in their
computational methods.  It's something I at least regard as a fairly
fundamental and important aspect of computation. And to me, that means
that the full power of the language should be applied toward beautifying,
simplifying, and otherwise enabling linear algebraic computations.


Cheers,
Bill
P.S.:   Please forgive the harangue-like nature of the post, it's the best
I could do at 3AM.

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-12 Thread Jerzy Karczmarczuk

Marcin Kowalczyk pretends not to understand:

> JK:
> 
> > Again, a violation of the orthogonality principle. Needing division
> > just to define signum. And of course a completely different approach
> > do define the signum of integers. Or of polynomials...
 
> So what? That's why it's a class method and not a plain function with
> a single definition.
> 
> Multiplication of matrices is implemented differently than
> multiplication of integers. Why don't you call it a violation of the
> orthogonality principle (whatever it is)?


1. Orthogonality priniciple has - in principle - nothing to do with
   the implementation.
   Separating a complicated structure in independent, or "orthogonal"
   concepts is a basic invention of human mind, spanning from the
   principle of Montesquieu of the independence of three political
   powers, down to syntactic issues in the design of a programming
language.

   If you eliminate as far as possible the "interfacing" between
concepts,
   the integration of the whole is easier. Spurious dependencies are
   always harmful.

2. This has been a major driving force in the construction of
mathematical
   entities for centuries. What do you really NEED for your proof. What
   is the math. category where a given concept can be defined, where
   a theorem holds, etc.

3. The example of matrices is inadequate (to say it mildly). The monoid
   rules hold in both cases, e.g. the associativity. So, I might call
   both operations "multiplication", although one is commutative, and
   the other one not.

==

In a later posting you say:

> If (+) can be implicitly lifted to functions, then why not signum?
> Note that I would lift neither signum nor (+). I don't feel the need.
 ...

I not only feel the need, but I feel that this is important that the
additive structure in the codomain is inherited by functions. In a more
specific context: the fact that linear functionals over a vector space
form also a vector space, is simply *fundamental* for the quantum 
mechanics, for the cristallography, etc. You don't need to be a Royal
Abstractor to see this. 



Jerzy Karczmarczuk
Caen, France

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-09 Thread Dylan Thurston

On Fri, Feb 09, 2001 at 12:55:12PM -0800, William Lee Irwin III wrote:
> class  (Eq a, Show a) => Num a  where
> (+), (-), (*)   :: a -> a -> a
> negate  :: a -> a
> abs, signum :: a -> a
> fromInteger :: Integer -> a
> fromInt :: Int -> a -- partain: Glasgow extension
>
> ...  So we have two totally inappropriate operations (fromInteger and
> fromInt), ...

I beg to differ on this point.  One could provide a default
implementation for fromInt(eger) as follows, assuming a 'zero' and
'one', which do obviously fit (they are the additive and
multiplicative units):

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

(Of course, one could use the algorithm in integer exponentiation to
make this efficient.)

Best,
Dylan Thurston



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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-09 Thread William Lee Irwin III

Fri, 09 Feb 2001 10:52:39 +, Jerzy Karczmarczuk pisze:
>> Again, a violation of the orthogonality principle. Needing division
>> just to define signum. And of course a completely different approach
>> do define the signum of integers. Or of polynomials...

On Fri, Feb 09, 2001 at 07:19:21PM +, Marcin 'Qrczak' Kowalczyk wrote:
> So what? That's why it's a class method and not a plain function with
> a single definition.
> 
> Multiplication of matrices is implemented differently than
> multiplication of integers. Why don't you call it a violation of the
> orthogonality principle (whatever it is)?

Matrix rings actually manage to expose the inappropriateness of signum
and abs' definitions and relationships to Num very well:

class  (Eq a, Show a) => Num a  where
(+), (-), (*)   :: a -> a -> a
negate  :: a -> a
abs, signum :: a -> a
fromInteger :: Integer -> a
fromInt :: Int -> a -- partain: Glasgow extension

Pure arithmetic ((+), (-), (*), negate) works just fine.

But there are no good injections to use for fromInteger or fromInt,
the type of abs is wrong if it's going to be a norm, and it's not
clear that signum makes much sense.

So we have two totally inappropriate operations (fromInteger and
fromInt), one operation which has the wrong type (abs), and an operation
which doesn't have well-defined meaning (signum) on matrices. If
we want people doing graphics or linear algebraic computations to
be able to go about their business with their code looking like
ordinary arithmetic, this is, perhaps, a real concern.

I believe that these applications are widespread enough to be concerned
about how the library design affects their aesthetics.


Cheers,
Bill
-- 
 Weak coffee is only fit for lemmas.
--

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



Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-09 Thread Marcin 'Qrczak' Kowalczyk

Fri, 09 Feb 2001 10:52:39 +, Jerzy Karczmarczuk <[EMAIL PROTECTED]> pisze:

> Again, a violation of the orthogonality principle. Needing division
> just to define signum. And of course a completely different approach
> do define the signum of integers. Or of polynomials...

So what? That's why it's a class method and not a plain function with
a single definition.

Multiplication of matrices is implemented differently than
multiplication of integers. Why don't you call it a violation of the
orthogonality principle (whatever it is)?

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


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



In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-09 Thread Jerzy Karczmarczuk

Marcin 'Qrczak' Kowalczyk wrote:


> JK> Now, signum and abs seem to be quite distincts beasts. Signum seem
> JK> to require Ord (and a generic zero...).
> 
> Signum doesn't require Ord.
> signum z = z / abs z
> for complex numbers.

Thank you, I know. And I ignore it. Calling "signum" the result of
a vector normalization (on the gauss plane in this case) is something
I don't really appreciate, and I wonder why this definition infiltrated
the prelude. Just because it conforms to the "normal" definition of
signum for reals?

Again, a violation of the orthogonality principle. Needing division
just to define signum. And of course a completely different approach
do define the signum of integers. Or of polynomials...


Jerzy Karczmarczuk

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