Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes
on 5 May 2000

>> Let us call for the recent basAlgPropos discussion a  hacker
>> any Haskell user who do not like to care of mathematics, especially, 
>> of its most abstract parts.
>> And call a  snob  any user that feels it quite different.

> How to call a person that does care about mathematics and about
> structure of numeric etc. types and classes in Haskell - but dislikes
> basAlgPropos, feeling it's extremely inelegant, complex, illogical
> and does not fit into the Haskell style at all?

Enemy of the people.  

>> Also one writes, for example,    zero x  
>> instead of                       zero `asTypeOf` x.

> Sample arguments are bad, because:
> [5 points follow]

But they are only for snobs. 
----------------------------
The only exceptions might be  zero, fromInteger.
And we could arrange that    0 :: a,  fromInteger :: Integer -> a
are as usual and
                       zero :: a -> a,  fromZ :: a -> Integer -> a
are only for  -fadvancedAlgebra.

Example when similar advanced things are needed: 
           computing with vectors in a space of variable dimension. 
See below.
Probably, the hackers will remain with old  0, fromInteger.

> 1. They present a confusing interface. This looks like a function,
>   but the real meaning is a constant. Neither mathematics nor
>   programming languages treat zero as a function from any unused
>   number to the zero value.

  zero `asTypeOf` x    is also a function applied to  x.
                       Where is the difference?

> 3. They don't add any functionality or expressiveness.

This is kind of wrong. See below.

> 5. They hurt performance, Not always they can be optimized out.

Why?  zero `asTypeOf` x   is as likely to be optimized as  zero x.
If for the former, the instance of `zero' is defined simply and can 
be, say in-lined, then the latter can too.

> 2. They usually make code larger [..]

Why would count this, people?

> 4. They make interfaces inconsistent. Some constants have sample
>   argument, some don't. Do you expext Nothing to have a sample
>   argument?!

You forget also to complain on that  negate  has one argument and 
                                     (*)     has too of them. 
Is this so painful: Nothing  has not sample argument, and zero  has?
Also what do you do with
                          class Foo a where weightOfType :: Int
?
Haskell would not allow to exploit it.
We are still forced to introduce something like
                          class Foo a where weightOfType :: a -> Int

> 4. [..] 
>   Even when a constant is overloaded
>   (instead of being only polymorphic), usually the exact type can be
>   deduced from usage. Haskell is not C++, it can infer types from
>   contexts of usage too.

This means that in many cases   zero
is automatically recognized as  zero `asTypeOf` what_is_detected.   
I agree. In many cases it is recognized, in many others does not.

This, - together with, as you point out,                `zero'  
is more natural than                                    `zero x',  
- I always considered as the arguments against `zero x'.
basAlgPropos  introduces `zero x' because
  * Haskell has problems with constants in methods, in particular
            `asTypeOf` is often needed,
  * `zero x'  fits the aim of implicit dynamic domains.

For snobs only
--------------
What the latter means:
two-dimensional vectors over Int can be modeled as  V_2 = (Int,Int)
And                                         zero :: V_2 = (0,0).

For the dimension 5, we have           V_5 = (Int,Int,Int,Int,Int),  
and                                    zero :: V_5 = (0,0,0,0,0).

What we have for the *variable dimension*  n ?
In a mathematical program, one often needs to compute in a vector
space of dimension  n,  where  n  is not given statically. Often 
it can only be defined at the run-time. Further, the user program 
often needs to compute things like
                          if  even $ dimension _ then ... else ...  

- find dimension of domain (space) and act dependently, say, on 
its evenness ...
I see only the following ways out

1. Ignore variable dimensions, generally, do not try at all to 
   model dynamic domains. Mostly, Haskell cannot support them. 

This is likely to bury 1/4 of computational mathematics.

2. For snobs only.
   ---------------
   Model implicit parametric domain.
   Only prepare to that in these domains some attributes are found
   at the run-time, and the membership to the domain may occur
   solvable only at run-time. The compiler would not support a 
   large part of this business, program the support yourself, use
   with special care.

  data Vector a = Vec [a] deriving(Eq,Show...)
  ...
  instance Additive a => Additive (Vector a) 
    where  
    (Vec xs)+(Vec ys) = Vec $ zip (+) xs ys
    zero (Vec xs)     = Vec $ map zero xs    -- ***
    ...
and consider  Vec [0,0]  and  Vec [0,0,0]  as of different domains.
Same type - but different domains.
And it exploits  `zero v':         zero $ Vec [0,0]
                                   zero $ Vec [0,0,0]
are not equal and belong to different implicit domains  V_2, V_3
inside the same type  Vector Int.
This agrees with mathematics and allows some support for computing 
in the space of "dimension n".

General reason:  a static type and class instances only 
                 cannot express certain very common part of practice 
                 of computation in algebraic domains.

And  basAlgPropos  is for the  Algebraic  part of the library.

For the above example, one could suggest to file all the vectors,
of length 0,1,2,... in one domain and compute things there.
But this would mean that the program does not understand good
"subspaces" of various dimension.

Adding one more example is likely to reject the doubts:
                Rse 2 3   and   Rse 2 4
represent the residues of  2
                       in domain  Z_3 = Integer modulo 3  (Z/(3))
                       and in     Z_4
The program often needs to operate in  Z/(m),  where  m  is 
computed at the run-time only. We have there:

      cardinality Z_3 = 3,  cardinality Z_4 = 4,
      1/2 = 2  in  Z_3:     inv (Rse 2 3) = Rse 2 3
                                                (2*2 =modulo 3= 1)
      and in  Z_4  it does not exist:  inv_m (Rse 2 4) = Nothing
 
This is why the sample arguments are so helpful.
Because with  -fadvancedAlgebra,  they are not "very sample", 
they contain important parameters describing domain.

But this all was only for  -fadvancedAlgebra.

The small question remains: how easy is to agree  -fadvancedAlgebra
items and all the rest.
General idea: 
     static Haskell instances do not allow part of mathematical 
     computation related to dynamic domains and provoke introduction
     of sample arguments for the advanced algebra.

For hackers
-----------
Ignore dynamic or implicit domains, ignore  
                                       data Vector a = Vec [a] ...
Only allow `zero x' for the key  -fadvancedAlgebra.
Maybe, we can arrange:
                    0  or `zero'        - as usual,
                    zeroS :: a -> a     - for  -fadvancedAlgebra
We have to see.

------------------
Sergey Mechveliani
[EMAIL PROTECTED]









Reply via email to