At Tue, 14 Jun 2011 19:52:00 -0700 (PDT),
o...@okmij.org wrote:
> 
> 
> Dan Doel wrote:
> >    class C a b | a -> b where
> >      foo :: a -> b
> >      foo = error "Yo dawg."
> >
> >    instance C a b where
> 
> The instance 'C a b' blatantly violates functional dependency and
> should not have been accepted. The fact that it was is a known bug in
> GHC. The bug keeps getting mentioned on Haskell mailing lists
> about every year. Alas, it is still not fixed. Here is one of the
> earlier messages about it:
> 
>   http://www.haskell.org/pipermail/haskell-cafe/2007-March/023916.html

But Oleg, isn't what you are complaining about *exactly* the lifting
of the coverage condition, which is one of the explicit points of
-XUndecidableInstances?  Are you advocating two separate switches for
lifting Paterson vs. Coverage?

What about the following code--do you think this should be illegal,
too?

        {-# LANGUAGE MultiParamTypeClasses #-}
        {-# LANGUAGE FunctionalDependencies #-}
        {-# LANGUAGE UndecidableInstances #-}

        class C a b c | a -> b where
        instance C (Maybe a) (Maybe b) (Maybe b) where

David

_______________________________________________
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime

Reply via email to