[Haskell-cafe] Re: FlexibleContexts and FlexibleInstances

David Menendez dave at zednenem.com
Thu Jun 11 13:44:43 EDT 2009


On Thu, Jun 11, 2009 at 4:16 AM, Claus Reinke<claus.reinke at talk21.com> wrote:
> |What you describe is exactly how I would *want* things to work. It's
> |nice to hear my wishes echoed from a user perspective. :-)
>
> actually, I was describing how things seem to work right now.
>
> |> Only MultiParamTypeClasses does (and neither extension is needed in the
> |> module defining 'f', if 'T' is imported, which suggests that
> |> MultiParamTypeClasses is propagated to importers - this isn't true for
> |> most other extensions). The documentation still points to -fglasgow-exts,
> so
> |> it doesn't seem to answer these questions..
> |
> |Right you are - which seems very strange to me. GHC accepts the module
> |defining 'f' with no flags at all, even though it is clearly not
> |Haskell 98. I'd go so far as to say that's a bug (as opposed to just
> |unwanted/unexpected behavior).
>
> It is not that strange, really (it ought to be documented, but the fan-
> out from glasgow-exts/hugs mode to more detailed extensions has
> been fairly recent, compared to the lifetime of these features):
>
> if module 'A' exports multiparameter type classes, importers of those
> classes have to have MultiParamTypeClasses on - there are no legal
> uses of those imports otherwise (while FlexibleInstances/Contexts can
> just affect a subset of use sites).

It's more complicated than that. If you have two modules A and B,
defined like so:

    {-# 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.


-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Glasgow-haskell-users mailing list