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







Reply via email to