Problem with functional dependencies
Chris Kuklewicz
haskell at list.mightyreason.com
Fri Nov 16 18:36:39 EST 2007
By the way, if you make the class C fundep declaration into:
> class C m f n | m f -> n where
then it compiles. This means ((M n) and (F n) imply N) and ("any m" and F'
imply N') which no longer conflict.
Daniel Gorín wrote:
> Hi
>
> I have some code that uses MPTC + FDs + flexible and undecidable
> instances that was working fine until I did a trivial modification on
> another part of the project. Now, GHC is complaining with a very
> confusing (for me, at least) error message. I've been finally able to
> reproduce the problem using these three small modules:
>
>> {-# LANGUAGE MultiParamTypeClasses #-}
>> {-# LANGUAGE FunctionalDependencies #-}
>> {-# LANGUAGE FlexibleInstances #-}
>> module M1
>>
>> where
>>
>> data M n = M
>> data F n = F
>>
>> class C m f n | m -> n, f -> n where
>> c :: m -> f -> Bool
>>
>> instance C (M n) (F n) n where
>> c _ _ = True
>
More information about the Glasgow-haskell-users
mailing list