S. Alexander Jacobson <[EMAIL PROTECTED]>  wrote

> Haskell doesn't seem to allow
>
>> instance Num (Int->Int) where ...
> or
>> instance Stringable String where ...
>
>How come?
>
>PS I am sure this has been discussed before, but I missed it...


First, Num, needs Eq to be defined. Consider

   module T where
   instance Eq  (Int->Int) where  f==g = (f 0)==(g 0)
   instance Num (Int->Int) where  f+g  = \x->(f x)+(g x)

Second, some compilers say at this:
"
(the instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
"
Maybe, they treat  Int Int  as a repeated variable?
At least, we may try to use some extension of Haskell-1.4.
For example in ghc, it helps  -fglasgow-exts.

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







Reply via email to