[Haskell-cafe] Re: FlexibleContexts and FlexibleInstances

Claus Reinke claus.reinke at talk21.com
Thu Jun 11 13:56:55 EDT 2009


>    {-# LANGUAGE MultiParamTypeClasses #-}
>    module A where
>    class Foo a b where  foo :: a -> b
> 
>    instance Foo Bool Int where
>        foo True = 1
>        foo False = 0
> 
>    module B where
>    import A
> 
>    bar :: (Foo a b) => [a] -> [b]
>    bar = map foo
> 
> I can load B.hs into GHCi and call bar without problems. So the import
> of Foo is fine. But you still get an error if you try to declare an
> instance of Foo in B.hs.
> 
>    instance Foo Bool Integer where
>        foo True = 1
>        foo False = 0
> 
> B.hs:8:0:
>    Illegal instance declaration for `Foo Bool Integer'
>        (Only one type can be given in an instance head.
>         Use -XMultiParamTypeClasses if you want to allow more.)
>    In the instance declaration for `Foo Bool Integer'
> Failed, modules loaded: A.

Ah, that is one definite bug waiting for a ticket, then:
- inheritance of MultiParamTypeClasses is not specified
- if it is inherited, the instance in B should be permitted
- if it is not inherited, the context in B should not be permitted

Claus




More information about the Glasgow-haskell-users mailing list