[Haskell-beginners] Re: Overlapping Instances

John Smith voldermort at hotmail.com
Mon Oct 25 16:00:34 EDT 2010


Thank you. Why does this code succeed for a, but stills fails on instance Show B? Do they not both invoke the same Show A?

{-# LANGUAGE TypeSynonymInstances, OverlappingInstances, IncoherentInstances #-}

import Data.Array

type A = Array Int Bool

data B = B A

instance Show A where
     show a = "foo"

instance Show B where
     show (B a) = show a

a = show $ listArray (1,3) $ repeat True

On 24/10/2010 16:37, Markus Läll wrote:
> Hi John,
>
> from what I gather this is because Show instance for "Array a b",
> which you are overlapping, is defined in a module without the
> OverlappingInstances declaration. Check the last few paragraphs of
> this from the GHC's user's guide:
>
> http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/type-class-extensions.html#instance-overlap
>
>
> Markus Läll
>
> On Sun, Oct 24, 2010 at 4:54 PM, John Smith<voldermort at hotmail.com>  wrote:
>> Following is a simplification of some code which I have written. I have an
>> overlapping Show instance for A, which is more specific than the general
>> instance for arrays, so I would expect it to be acceptable as an overlapping
>> instance. Nevertheless, I get the following compiler error:
>>
>>     Overlapping instances for Show A
>>       arising from a use of `show' at 13:17-22
>>     Matching instances:
>>       instance (Ix a, Show a, Show b) =>  Show (Array a b)
>>         -- Defined in GHC.Arr
>>       instance [overlap ok] Show A -- Defined at 9:9-14
>>     In the expression: show a
>>     In the definition of `show': show (B a) = show a
>>     In the instance declaration for `Show B'
>> Compilation failed.
>>
>> I've tried UndecidableInstances and IncoherentInstances, but they don't seem
>> to help. What am I doing wrong?
>>
>> Many thanks in advance for any assistance.
>>
>> -John
>>
>> {-# LANGUAGE TypeSynonymInstances, OverlappingInstances #-}
>>
>> import Data.Array
>>
>> type A = Array Int Bool
>>
>> data B = B A
>>
>> instance Show A where
>>     show a = "foo"
>>
>> instance Show B where
>>     show (B a) = show a



More information about the Beginners mailing list