[Haskell-cafe] Repeating type variables in MultiParamTypeClasses instance heads
Finn Teegen
fte at informatik.uni-kiel.de
Fri May 7 07:48:59 UTC 2021
Even without a method you can trigger the overlapping error. Consider
the following program.
class C a b c
instance C [a] [a] [b]
instance C [a] [b] [b]
f :: C a b c => a -> b -> c -> Bool
f _ _ _ = True
g = f [True] [True] [True]
The use of 'f' in 'g' produces the following message.
Overlapping instances for D [Bool] [Bool] [Bool]
arising from a use of âfâ
Matching instances:
instance D [a] [a] [b]
instance D [a] [b] [b]
⢠In the expression: f [True] [True] [True]
Cheers,
Finn
On 06/05/2021 23:05, Viktor Dukhovni wrote:
> On Thu, May 06, 2021 at 10:51:32PM +0200, Henning Thielemann wrote:
>
>> {-# LANGUAGE MultiParamTypeClasses #-}
>> module FlexibleInstance where
>>
>> class C a b c where
>
> This class has an empty interface, it just builds triples of types that
> imply a constraint. No matter how many such triples one creates, there
> can't be any conflict between them.
>
>> instance C [a] [a] [b] where
>> instance C [a] [b] [b] where
>
> These don't conflict.
>
More information about the Haskell-Cafe
mailing list