[Haskell-cafe] Class constraints with "free" type variables and fundeps

Francesco Mazzoli f at mazzo.li
Fri Sep 28 18:36:49 CEST 2012


I would expect this to work, maybe with some additional notation (a la
ScopedTypeVariables)

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

    class Foo a b | a -> b

    class Foo a b => Bar a where
        foo :: a -> b -> c

The type family equivalent works as expected:

    {-# LANGUAGE TypeFamilies #-}

    class Foo a where
        type T a :: *

    class Bar a where
        foo :: a -> T a -> c

I can't use type families because the `Foo' I'm using is in an external library.
Is there any way to achieve what I want without adding `b' to `Bar'?

--
Francesco * Often in error, never in doubt



More information about the Haskell-Cafe mailing list