This fails to compile. Oddly enough, if you remove the instance 
declaration (1), or if you remove the r parameter to T, or if you do any 
of the other simplifications I've tried, it compiles successfully.

-- ghc -fglasgow-exts -fallow-undecidable-instances -c WeirdInsts.hs
module WeirdInsts where
    {
    data T r = MkT;

    class C t;

    class D b t;

    instance (C (T r)) => D b (T r); -- (1)

    class F a b | a -> b;

    f :: (F a b,D b t) => (a,t);
    f = undefined;

    g :: (F a b,D b (T r)) => (a,T r);
    g = f;
    }

$ ghc -fglasgow-exts -fallow-undecidable-instances -c WeirdInsts.hs

WeirdInsts.hs:18:
    Could not deduce (C (T r)) from the context (F a b, D b (T r))
      arising from use of `f' at WeirdInsts.hs:18
    Probable fix:
        Add (C (T r)) to the type signature(s) for `g'
        Or add an instance declaration for (C (T r))
    In the definition of `g': g = f

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.0.1

-- 
Ashley Yakeley, Seattle WA

_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to