improving confusion with types of `foo'

1995-09-19 Thread Sergei D. Meshveliani


Yesterday I had sent certain suggestion for the Haskell prelude. 
Then I recalled it and found it rubbishy.

It concerned changing `Ordering' to `Compare' for the result type 
of `compare' in Haskell 1.3  and the function  foo  having the type
Foo.

Improving a confusion:

`Ordering' is not a type of function `compare', but only of its
result.
So the suggestion might be to call it  Compare_res  instead.

Generally, the result type of  foo  might be called  Foo_res.

This makes sense when the type is designed only as a holder for the  
foo  values.

But now I do not know whether this  Foo_res  worth worrying.

Old Haskell may relax.



S.M.










suggestion for Haskell prelude

1995-09-18 Thread Sergei D. Meshveliani


A very small suggestion for the Haskell prelude style:

if a type has no meaning except being a holder for the values
of the function  foo,  then let the type be called  Foo.

This will economize names.

Thus the type of `compare' from 1.3 prelude should be called  Compare,
etc.



Sergey Mechveliani

[EMAIL PROTECTED]





suggestion to Haskell standard

1995-09-11 Thread Sergei D. Meshveliani


Suggestion for Standard Prelude.

To replace such standard prelude functions as  min,minimum,sort  etc.  
with their "function-argument" variants.
For example:

data  Compare = LT | GT | EQ

sort :: (a -> a -> Compare) -> [a] -> [a]
 -- cp xs 


cp x y -> LTif  x  is less than  y,
  GT  greater,
  EQ  otherwise (suppose we have not Eq !).


Probably, some other functions need similar generalization.



Argumentation.

1.
Prelude already enjoys such a functions as  break p xs,  filter p xs
etc.  
Why should we leave this style ?  It may lead to complications only 
if we introduce too many of such  p -s.

2. 
"function-argument" variants look more flexy and general than the 
formats like
   (Ord a) => [a] -> [a]

- because if we have  Ord a,  then we may always call  

sort cp xs   where  cp x y | xy   = GT
   | otherwise = EQ
( or simply, sort compare xs
  - for Haskell-1.3.  - if I recall the right name `compare'
)

and obtain what we had in the old version.

The inverse inclusion does not hold: 
  we cannot supply the same type  a  with many  Ord instances,
  whereas we may call  sort  with many different  cp -s  on the 
  same  xs :: [a].


Am I missing something ?

--

Further, what I fear the most is that the suggestion would be 
accepted, and these new versions join the old ones !
For really, the prelude contains to many functions.


Serge D.Mechveliani

[EMAIL PROTECTED]







adding instances to (,)

1995-07-24 Thread Sergei D. Meshveliani


Dear sir,


I had written several pages of Haskell scripts, tried  HUGS Haskell
on them, debugged, and now I'm trying to complile the stuff with 
Glasgow Haskell.

ghc-0.25  dislikes the following declarations:

-
module  M  where

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

This module only tries to export the instance for  (,):

(Num a, Num b) =>  Num (a,b)  



HUGS Haskell  (it ignores modularity)  makes this  (+)  for pairs
all right, so one can evalute  (1,1)+(1,2) -> (2,3).


But  ghc-0.25
says that this instance for Num should be declared in the same
module where the type constructor is defined.

I guess, it is the  (,)  constructor from the  Prelude  module.

Should one add an instance of  Num for  (,)  to  Prelude ?

And how to do this ?


Haskell-1.3 report contains an example:

--
module A where
import Prelude hiding (map)
map f x = x f
--

This module redefines  `map'  totally.

Should I redefine totally  (,)  with its instances in this way ?

Besides,  import Prelude hiding ( (,) )  

is qualified as illegal syntax.

Does this all mean that to overload (+) for pairs one should 
define some new constructor, isomorphic to  (,)  but with the
additional instances ?  This does not look nice ...


Thanks in advance.

Sergei D.Meshveliani










Haskell & Gofer & multiple parameters

1995-06-27 Thread Sergei D. Meshveliani


[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   whereadd  :: a -> a -> a
  zero ...
  ...

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

class  (AddGroup a, Field c) =>  VectorSpace a cwhere
  
  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   a