In ghc 6.10.1 the ~ constraint is working:

{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}

module D where

instance (Num a, Num b, a ~ b) => Num (a,b) where
    (x,y) * (u,v) = (x*u-y*v, x*v+y*u)

test1 = (1,1) * (2,2)

test2 = (1,1.0)*(2,2)

With ghci:

*D> test1
test1
(0,4)
*D> test2
test2
(0.0,4.0)
*D> :t test1
:t test1
test1 :: (Integer, Integer)
*D> :t test2
:t test2
test2 :: (Double, Double)

--
Chris

_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to