[EMAIL PROTECTED]


Hi,

Alain M. Gaudrault  <[EMAIL PROTECTED]>  writes
in his letter of  26 Jun 1995 16:55


> 1) let  fred x = x  in  fred fred;

> Haskell complains:
> [55] Ambiguously overloaded tyvar(s) in class(es) Text in  
> show (let { fred = \A1_fred -> A1_fred
>  } in fred fred)

[...]

> 2) I'm attempting to add another instance to the Num class as a
>    test of Haskell's OOP functionality.  
>    Thus, I create a new type which is a 3-tuple:

> data ThreeSpace = TS (Integer, Integer, Integer);

> Then, for each of the methods required by Num, a function is 
> defined for the new type ...

>let  addTS (TS (x1,x2,x3)) (TS (y1,y2,y3)) = 
                                  TS ((x1+y1),(x2+y2),(x3+y3)) ;;

>let  fIntegerTS x =  TS ((fromInteger x), 0, 0);;

[...]

>Now, I need to add the ThreeSpace instance to Num:

>instance  Num ThreeSpace  where
>(+) = addTS
>negate = negTS
>fromInteger = fIntegerTS
[...]
;

> This is where things crap out.  I get the following error:
> [56] Not an instance Num ThreeSpace in 
> ((DD.Num.$fromInteger{FARITY 1}))::(Integer, Int, Double) -> ThreeSpace
> in $fromInteger

---------------------------------------------------------------------

I had a question similar to  2)  dealing with  Gofer. 

I believe the experts will explain the things. 

Here are my impressions.

---------------------------------------------------------------------

Concerning the question  1) :

            let  f x = x  in   f f    

returns something like  {v121}  in GOFER,  which I guess is the
denotation for the function  (lambda (x) x).  And it applies all 
right:
            let  f x = x  in  (f f) 2    -->   2    

So indeed, let Haskell explain the subject.
---------------------------------------------------------------------

Question 2.

Similarly, a couple of months ago I tried to define  Num  for
the type like 
                 data  SP = SP Int Int 
in GOFER.
First it resisted strongly.  Then I studied   "standard.prelude".
It declares
                 class  Text a =>  Num a   ...

which means that, for example, before defining  Num  members for  
SP  one should define the  Text class  for it.

So I put cynically:
------------------
intance   Text SP            -- empty definitions !

instance  Num SP   where    (SP n m)+(SP n1 m1) = SP (n+n1) (m+m1)
-------------------

and it all improved.

------------------------------------------------------------------
------------------------------------------------------------------



I have some problems too.
I had written a hundred of pages of Gofer scripts and found it very 
nice.
Still I am a novice in Gofer, Haskell. 

I intend to try Haskell hoping for the benefits of modularity and
arbitrary length integers.

Here is my question to Haskell.

    What is the substitution for the programming style using 
    the multiple parameters in classes and instances ?


Example 1.

instance  (Num a, Num b) =>  Num (a,b)  where 
                                      (x,y)+(x1,y1) = (x+x1,y+y1)

Would Haskell allow this ?
And if the Cartesian product is a special constructor, than how 
the similar construction will do for some user type, say  
SP a b  ?


Example 2.

In mathematics, a Vector Space is defined as a tripple  {a,c,cM}, 
where
a   is a commutative additive group of Vectors ((+),(-),zero),
c   is the Field of coefficients  (+,-,*,zero,unity,inverse),
cM  is the multiplication-by-coefficient low  ::  c -> a -> a

- and these objects should satisfy certain properties ...

So I put in Gofer :

----------------------------------------------------------
class  Eq a =>  AddGroup a   where    add  :: a -> a -> a
                                      zero ...
                                      ...

class  AddGroup a => Field a  where   mul   :: a -> a -> a
                                      unity :: ...
                                      ...

class  (AddGroup a, Field c) =>  VectorSpace a c    where
  
  coefMul :: c -> a -> a
----------------------------------------------------------
  

I wonder how this can be expressed without multiple parameters ?


I had tried to represent an instance of vector space as a type

data  VS a c =  VS a c (c->a->a)

- it is like a tripple where the third element is a coefficient 
multiplication low.  Further,

class  Field v  =>  VectorSpace V    
  where
  coefMul :: v -> v
  ...

Here the vectors and coefficients are somehow mixed in a single 
type  v.

Then I try to define the  VectorSpace instances for the instances
of the general type  VS.
Let, it be, for example the two-dimension space over rationals :
-------------------------------
type  RR  =  (Rational,Rational)

type  VR2 =  VS RR Rational mulR2

mulR2 r (r1,r2) = (r*r1,r*r2)
------------------------------

First, the coefficients form a field. Hence we are forced to declare
that  VS  is a field, and extend (*) to the whole VS while it 
actually ignores the parts of  (VS vec coef cMul)  except  coef.
  Further, the addition   add   acts on the whole   VS,  only it is 
defined so that  vec  and   coef  parts add each in its own way.
So  add  serves for both additions simulteneousely.


The Second problem:

we need to operate with the two different equalities "inside" VS:
(==)  for the Vector parts  vec  of   (VS vec coef cMul)   and
(==)  for the coefficient parts   coef  of it.

This difference it expressed automatically through the use of
multiple parameters.

In other case, the whole  VS  is declared to be a Field,  which 
requires one the same (==) for VS.

You see, "vectors u,v are equal"  and, say,  "pairs (u,c1),(v,c2) 
are equal"  mean very different things ...

The impression is that something is wrong here. 

What is the way out ?

So far I use Gofer and multiple parameters (and often fall into
confusion !) and had not thought long on the subject.

But what the loss may be when I try Haskell ?



I will appreciate any reasonable advice.


Regards,

Sergei.D.Meshveliani




Reply via email to