Doug McIlroy wrote: > A fragment of an attempt to make pairs serve as complex numbers, > using ghc/hugs extensions: > > instance Num a => Num (a,a) where > (x,y) * (u,v) = (x*u-y*v, x*v+y*u) > > Unfortunately, type inference isn't strong enough to cope with > > (1,1)*(1,1)
It is not quite difficult to tell the type checker that if pairs of numbers are numbers, the two components of the pair must have the same type. We say so literally. We first should make the instance more general to permit any pair, of the type (a,b) to match. We next impose the constraint that the types a and b must be in the class Num; furthermore, the types a and b must be the same. Here is the complete solution that should work on GHC 6.4, 6.6, 6.8, and probably of earlier and later versions. > {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, > UndecidableInstances, FlexibleInstances #-} > > module D where > > instance (Num a, Num b, TypeCast b a, TypeCast a b) => Num (a,b) where > (x,y) * (u,v) = (typeCast x * typeCast u - typeCast y * typeCast v, > typeCast x * typeCast v + typeCast y * typeCast u) > (x,y) + (u,v) = (typeCast x + typeCast u, > typeCast y + typeCast v) > (x,y) - (u,v) = (typeCast x - typeCast u, > typeCast y - typeCast v) > fromInteger x = (fromInteger x, 0) > > test1 = (1,1) * (2,2) -- (0.0,4.0) > test2 = (1.1,1) * (2,2) -- (0.20000000000000018,4.2) > test3 = test1 * test2 -- (-16.8,0.8000000000000007) > test4 = (test1 + test3) * (test1 - test3) -- (-297.6,26.880000000000024) > test4' = -16 - test3 * test3 -- (-297.6,26.880000000000024) > > class TypeCast a b | a -> b, b->a where typeCast :: a -> b > class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b > class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b > instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x > instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' > instance TypeCast'' () a a where typeCast'' _ x = x As one can see, we added typeCast before every variable, indicating that an application of the equality constraint is needed. We let the GHC figure out what should be `cast' to what. The recent versions of GHC have a nifty equality constraint, so the code can be written simply > {-# 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) It does typecheck in GHC 6.8.2; alas, running the code produces > ghc-6.8.2: panic! (the 'impossible' happened) > (GHC version 6.8.2 for i386-unknown-freebsd): > nameModule $dNum{v aJiF} I guess one needs to upgrade to GHC 6.10. The solution using TypeCast, however inelegant, works on GHC 6.8 and earlier compilers. _______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell