[Haskell-cafe] tricky recursive type instance method

Antoine Latter aslatter at gmail.com
Fri Jan 28 05:33:54 CET 2011


On Thu, Jan 27, 2011 at 10:09 PM, Frank Kuehnel <kuehnelf at gmail.com> wrote:
> Hi Antoine,
>
> I've turned on the OverlappingInstances option
>
> this is what I get, when I execute
>
>> conj ((C 1 2) :: (Complex Int))
>
>    Overlapping instances for DAlgebra (Complex Float) (Complex Float)
>      arising from a use of `conj'
>    Matching instances:
>      instance [overlap ok] Real a => DAlgebra a a
>        -- Defined at Clifford.hs:21:10-31
>      instance [overlap ok] (Real r, Num a, DAlgebra a r) =>
>                            DAlgebra (Complex a) r
>

I'm guessing GHC can't pick which instance to use, because neither one
follows the rules for being more specific than the other. I tried to
read the manual on it, but I don't have a clear answer for you:
http://www.haskell.org/ghc/docs/7.0.1/html/users_guide/type-class-extensions.html#instance-overlap

If I change the `DAlgebra a a` instance to `DAlgebra Integer Integer`
I can get examples to work fine.

Antoine

>
> On Jan 27, 2011, at 8:00 PM, Antoine Latter wrote:
>
>> On Thu, Jan 27, 2011 at 9:35 PM, Frank Kuehnel <vincef13 at mac.com> 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)
>>>
>>
>>
>> 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 at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>
>



More information about the Haskell-Cafe mailing list