multi-parameter typeclass with default implementation

Hi, I struggle with a dummy example using a multi-parameter typeclass containing a default implementation for a function: --------------------------------------- {-# LANGUAGE MultiParamTypeClasses #-} class Foo a b where bar :: a -> Int foobar :: a -> b -> Int foobar avalue bvalue = bar avalue instance Foo Int Int where bar i = 5 main = do print $ bar (4::Int) --------------------------------------- I obtain the following errors. I have tried various things without any success. Any help appreciated! Thanks TP PS: The errors: $ runghc test.hs test.hs:8:28: Could not deduce (Foo a b1) arising from a use of `bar' from the context (Foo a b) bound by the class declaration for `Foo' at test.hs:(3,1)-(8,37) The type variable `b1' is ambiguous Possible fix: add a type signature that fixes these type variable(s) In the expression: bar avalue In an equation for `foobar': foobar avalue bvalue = bar avalue test.hs:16:9: No instance for (Foo Int b0) arising from a use of `bar' The type variable `b0' is ambiguous Possible fix: add a type signature that fixes these type variable(s) Note: there is a potential instance available: instance Foo Int Int -- Defined at test.hs:10:10 Possible fix: add an instance declaration for (Foo Int b0) In the second argument of `($)', namely `bar (4 :: Int)' In a stmt of a 'do' block: print $ bar (4 :: Int) In the expression: do { print $ bar (4 :: Int) }

TP
Hi,
I struggle with a dummy example using a multi-parameter typeclass containing a default implementation for a function:
--------------------------------------- {-# LANGUAGE MultiParamTypeClasses #-}
class Foo a b where
bar :: a -> Int
The problem is in this declaration, which does not mention the type "b". This makes it impossible for the compiler to infer which instance to use when "bar" is used. This is what the compiler is trying to tell you when it says "The type variable `b1' is ambiguous". As far as I know, you'd need to do something like this to accomplish what you are after, {-# LANGUAGE MultiParamTypeClasses, DefaultSignatures #-} class Bar a where bar :: a -> Int class FooBar a b where foobar :: a -> b -> Int default foobar :: Bar a => a -> b -> Int foobar avalue bvalue = bar avalue instance Bar Int where bar i = 5 instance FooBar Int Int main = do print $ bar (4::Int) print $ foobar (5::Int) (2::Int) Cheers, - Ben

Ben Gamari wrote:
{-# LANGUAGE MultiParamTypeClasses #-}
class Foo a b where
bar :: a -> Int
The problem is in this declaration, which does not mention the type "b". This makes it impossible for the compiler to infer which instance to use when "bar" is used. This is what the compiler is trying to tell you when it says "The type variable `b1' is ambiguous".
Thanks, this works perfectly. Yet, to try to improve myself, I would like to discuss a bit on the text of the two obtained errors in my example (correct me if I am wrong below). """ test.hs:16:9: No instance for (Foo Int b0) arising from a use of `bar' """ The second error is clear: indeed by calling `bar` on `4::Int`, we don't indicate the type of b allowing to choose the right typeclass for the implementation of the `bar` function. The fact there is only one typeclass instance with Int as type for type variable `a` does not change anything: Haskell does not look at the implemented instances. In other words, ”typeclasses are open”: more typeclasses with Int as first type variable (and types different from `Int` for type variable `b`) may be added in the future, and Haskell asks to specify which one is to use now, not in the future. (Is this the right meaning for "typeclasses are open"?). """ test.hs:8:28: Could not deduce (Foo a b1) arising from a use of `bar' from the context (Foo a b) bound by the class declaration for `Foo' at test.hs:(3,1)-(8,37) The type variable `b1' is ambiguous """ Is this the same interpretation here? That is, even in the default implementation of a typeclass function, Haskell does not suppose that the instance of `bar` to use is the one of the considered instance? Thanks a lot, TP

Ben Gamari wrote:
As far as I know, you'd need to do something like this to accomplish what you are after,
{-# LANGUAGE MultiParamTypeClasses, DefaultSignatures #-}
class Bar a where bar :: a -> Int
class FooBar a b where foobar :: a -> b -> Int default foobar :: Bar a => a -> b -> Int foobar avalue bvalue = bar avalue
instance Bar Int where bar i = 5 instance FooBar Int Int
main = do print $ bar (4::Int) print $ foobar (5::Int) (2::Int)
It seems that the "DefaultSignatures" extension is not necessary, the following version works correctly on my computer (ghc 7.6.2): ------- {-# LANGUAGE MultiParamTypeClasses #-} class Bar a where bar :: a -> Int class FooBar a b where foobar :: Bar a => a -> b -> Int foobar avalue bvalue = bar avalue instance Bar Int where bar i = 5 instance FooBar Int Int main = do print $ bar (4::Int) print $ foobar (5::Int) (2::Int) -------

On 20/08/13 12:13, TP wrote:
{-# LANGUAGE MultiParamTypeClasses #-}
class Bar a where bar :: a -> Int
class FooBar a b where foobar :: Bar a => a -> b -> Int foobar avalue bvalue = bar avalue
instance Bar Int where bar i = 5 instance FooBar Int Int
main = do print $ bar (4::Int) print $ foobar (5::Int) (2::Int)
It might be better to make Bar a superclass of FooBar, class Bar a => FooBar a b where foobar :: a -> b -> Int foobar a b = bar a Then the compiler knows that every instance of FooBar also requires an instance of Bar. Twan

Ben Gamari wrote:
{-# LANGUAGE MultiParamTypeClasses, DefaultSignatures #-}
In fact, we could try a solution using a simple parameter typeclass containing an implicit existential type b (I hope I am right): ------------------------- class Foo a where bar :: a -> Int foobar :: Foo b => a -> b -> Int foobar avalue bvalue = bar avalue instance Foo Int where bar i = 5 foobar avalue bvalue = (bar avalue) + (bar bvalue) main = do print $ bar (4::Int) print $ foobar (5::Int) (3::Int) ------------------------- It works correctly: $ runghc test_one_simple_parameter_typeclass.hs 5 10 But if we try to call a function external to the typeclass: ------------------------- toto :: Int -> Int toto i = 4 class Foo a where bar :: a -> Int foobar :: Foo b => a -> b -> Int foobar avalue bvalue = bar avalue instance Foo Int where bar i = 5 foobar avalue bvalue = (bar avalue) + (bar bvalue) + (toto bvalue) main = do print $ bar (4::Int) print $ foobar (5::Int) (3::Int) ------------------------- We get an error message (see below) meaning that when we call "toto" with "bvalue", there is not guarantee that "bvalue" is an "Int". So, in this situation, *are we compelled to use multiparameter typeclasses*? PS: the error message yielded by the second example above: $ runghc test_one_simple_parameter_typeclass_limitation.hs test_one_simple_parameter_typeclass_limitation.hs:15:37: Could not deduce (b ~ Int) from the context (Foo b) bound by the type signature for foobar :: Foo b => Int -> b -> Int at test_one_simple_parameter_typeclass_limitation.hs:(13,5)-(15,43) `b' is a rigid type variable bound by the type signature for foobar :: Foo b => Int -> b -> Int at test_one_simple_parameter_typeclass_limitation.hs:13:5 In the first argument of `toto', namely `bvalue' In the second argument of `(+)', namely `(toto bvalue)' In the expression: (bar avalue) + (bar bvalue) + (toto bvalue)

You could also use functional dependencies here: {-# LANGUAGE FunctionalDependencies #-} class Foo a b | a -> b where bar :: a -> Int foobar :: a -> b -> Int foobar avalue bvalue = bar avalue instance Foo Int Int where bar i = 5 main = print $ bar (4::Int) Here you are saying that the type parameter b is determined by the parameter a, so GHC knows that the instance Foo Int Int is the only instance of Foo with a = Int, thus removing the ambiguity. -- Erlend Hamberg ehamberg@gmail.com
participants (4)
-
Ben Gamari
-
Erlend Hamberg
-
TP
-
Twan van Laarhoven