
Well, it seems that you can't do exactly what you want. So, the simplest way to do this would be not to make Foo a superclass for Bar:
class Bar a where
foo :: Foo a b => a -> b -> c
Then you would have to mention Foo everywhere.
If you really need, for some reason, to ensure that every Bar instance has a corresponding Foo instance, you can do some oleging this way:
data Void b = Void
data FooEv a where FooEv :: Foo a b => Void b -> FooEv a
class Bar a where
barFoo :: FooEv a
bar :: Foo a b => a -> b -> c
Then, whenever you need Foo methods, you can do pattern-matching:
case barFoo :: FooEv a of
FooEv (Void :: Void b) -> …
Now some "b" is in scope, and there is an instance of Foo a b.
On Sep 28, 2012, at 8:36 PM, Francesco Mazzoli
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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe