1 {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
2 FlexibleInstances, UndecidableInstances #-}
3 -- UndecidableInstances because (L a b) is no smaller than (C a b)
5 -- This one shows up another rather subtle functional-dependecy
8 -- Could not deduce (C a b') from the context (C a b)
9 -- arising from the superclasses of an instance declaration at Foo.hs:8:0
10 -- Probable fix: add (C a b') to the instance declaration superclass context
11 -- In the instance declaration for `C (Maybe a) a'
13 -- Since L is a superclass of the (sought) constraint (C a b'), you might
14 -- think that we'd generate the superclasses (L a b') and (L a b), and now
15 -- the fundep will force b=b'. But GHC is very cautious about generating
16 -- superclasses when doing context reduction for instance declarations,
17 -- becasue of the danger of superclass loops.
19 -- So, today, this program fails. It's trivial to fix by adding a fundep for C
20 -- class (G a, L a b) => C a b | a -> b
22 -- Note: Sept 08: when fixing Trac #1470, tc138 started working!
23 -- This test is a very strange one (fundeps, undecidable instances),
24 -- so I'm just marking it as "should-succeed". It's not very clear to
25 -- me what the "right" answer should be; when we have the type equality
26 -- story more worked out we might want to think about that.
28 module ShouldFail
where
32 class (G a
, L a b
) => C a b
34 instance C a b
' => G
(Maybe a
)
35 instance C a b
=> C
(Maybe a
) a
36 instance L
(Maybe a
) a