tricky recursive type instance method

Hi folks, how do I make this work: I want a division algebra over a field k, and I want to define the conjugation of complex numbers, i.e. conj (C 1 2) but also the conjugation of tensors of complex numbers conj (C (C 1 2) (C 1 4)) ghci load that stuff butt barfs on a simple
conj (C 1 2)
with instance Real a => DAlgebra a a -- Defined at Clifford.hs:20:10-31 instance (Real r, Num a, DAlgebra a r) => DAlgebra (Complex a) r here's the code: -- for a normed division algebra we need a norm and conjugation! class DAlgebra a k | a -> k where -- need functional dependence because conj doesn't refer to k conj :: a -> a abs2 :: a -> k -- real numbers are a division algebra instance Real a => DAlgebra a a where conj = id abs2 x = x*x -- Complex numbers form a normed commutative division algebra data Complex a = C a a deriving (Eq,Show) instance Num a => Num (Complex a) where fromInteger a = C (fromInteger a) 0 (C a b)+(C a' b') = C (a+a') (b+b') (C a b)-(C a' b') = C (a-a') (b-b') (C a b)*(C a' b') = C (a*a'-b*b') (a*b'+b*a') instance (Real r, Num a, DAlgebra a r) => DAlgebra (Complex a) r where conj (C a b) = C a (conj (-b)) abs2 (C a b) = (abs2 a) + (abs2 b) Thanks for you help!

On Thu, Jan 27, 2011 at 9:35 PM, Frank Kuehnel
Hi folks,
how do I make this work: I want a division algebra over a field k, and I want to define the conjugation of complex numbers, i.e. conj (C 1 2) but also the conjugation of tensors of complex numbers conj (C (C 1 2) (C 1 4))
ghci load that stuff butt barfs on a simple
conj (C 1 2)
with instance Real a => DAlgebra a a -- Defined at Clifford.hs:20:10-31 instance (Real r, Num a, DAlgebra a r) => DAlgebra (Complex a) r
here's the code:
-- for a normed division algebra we need a norm and conjugation! class DAlgebra a k | a -> k where -- need functional dependence because conj doesn't refer to k conj :: a -> a abs2 :: a -> k
-- real numbers are a division algebra instance Real a => DAlgebra a a where conj = id abs2 x = x*x
-- Complex numbers form a normed commutative division algebra data Complex a = C a a deriving (Eq,Show)
instance Num a => Num (Complex a) where fromInteger a = C (fromInteger a) 0 (C a b)+(C a' b') = C (a+a') (b+b') (C a b)-(C a' b') = C (a-a') (b-b') (C a b)*(C a' b') = C (a*a'-b*b') (a*b'+b*a')
instance (Real r, Num a, DAlgebra a r) => DAlgebra (Complex a) r where conj (C a b) = C a (conj (-b)) abs2 (C a b) = (abs2 a) + (abs2 b)
What error are you getting in GHCi? It wasn't immediately clear from your email, but maybe I missed it. It looks like you have overlapping instances between `DAlgebra a a` and `DAlgebra (Complex a) r`, so if that's what you want you'll need to making sure you have the OverlappingInstances extension turned on. You might run in to other issues further on. Antoine
Thanks for you help!
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, you might want to take a look at [1]AdvancedOverlap. However, the most simple option would be to wrap up your (Real a => DAlgebra a a) instance in a newtype:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype FromReal a = FromReal a deriving (Eq, Ord, Read, Show, Num, Real)
instance Real a => DAlgebra (FromReal a) (FromReal a) where conj = id abs2 x = x*x
Steffen [1] http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap On 01/28/2011 04:35 AM, Frank Kuehnel wrote:
Hi folks,
how do I make this work: I want a division algebra over a field k, and I want to define the conjugation of complex numbers, i.e. conj (C 1 2) but also the conjugation of tensors of complex numbers conj (C (C 1 2) (C 1 4))
ghci load that stuff butt barfs on a simple
conj (C 1 2)
with instance Real a => DAlgebra a a -- Defined at Clifford.hs:20:10-31 instance (Real r, Num a, DAlgebra a r) => DAlgebra (Complex a) r
here's the code:
-- for a normed division algebra we need a norm and conjugation! class DAlgebra a k | a -> k where -- need functional dependence because conj doesn't refer to k conj :: a -> a abs2 :: a -> k
-- real numbers are a division algebra instance Real a => DAlgebra a a where conj = id abs2 x = x*x
-- Complex numbers form a normed commutative division algebra data Complex a = C a a deriving (Eq,Show)
instance Num a => Num (Complex a) where fromInteger a = C (fromInteger a) 0 (C a b)+(C a' b') = C (a+a') (b+b') (C a b)-(C a' b') = C (a-a') (b-b') (C a b)*(C a' b') = C (a*a'-b*b') (a*b'+b*a')
instance (Real r, Num a, DAlgebra a r) => DAlgebra (Complex a) r where conj (C a b) = C a (conj (-b)) abs2 (C a b) = (abs2 a) + (abs2 b)
Thanks for you help!
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Frank Kuehnel schrieb:
Hi folks,
how do I make this work: I want a division algebra over a field k, and I want to define the conjugation of complex numbers, i.e. conj (C 1 2) but also the conjugation of tensors of complex numbers conj (C (C 1 2) (C 1 4))
ghci load that stuff butt barfs on a simple
conj (C 1 2)
with instance Real a => DAlgebra a a -- Defined at Clifford.hs:20:10-31 instance (Real r, Num a, DAlgebra a r) => DAlgebra (Complex a) r
here's the code:
-- for a normed division algebra we need a norm and conjugation! class DAlgebra a k | a -> k where -- need functional dependence because conj doesn't refer to k conj :: a -> a
Since conj does not need type 'k' I would separate it from class DAlgebra.
abs2 :: a -> k
-- real numbers are a division algebra instance Real a => DAlgebra a a where conj = id abs2 x = x*x
-- Complex numbers form a normed commutative division algebra data Complex a = C a a deriving (Eq,Show)
This is the way, we defined Complex in NumericPrelude. We have no RealFloat constraint there in order to allow Gaussian numbers and other types.
participants (4)
-
Antoine Latter
-
Frank Kuehnel
-
Henning Thielemann
-
Steffen Schuldenzucker