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










Re: adding instances to (,)

1995-07-24 Thread peterson-john


Your error messages from ghc are correct: you have violated the
infamous C-T rule (section 4.3.2, page 32) which restricts instance
declarations to the module containing either the class or the
datatype.  Since (,) and Num are both in the prelude, you can't
compile this in official Haskell 1.2.  You could define your own
datatype isomorphic to (,) but you won't get the nice notation.

This should be legal in Haskell 1.3 (once it's done!) - the C-T rule
can be quite annoying so it's being relaxed.

Just remember: HUGS is not Haskell  :-).


  John Peterson
  Yale Haskell Project