[Haskell-beginners] multi-parameter typeclass with default implementation
TP
paratribulations at free.fr
Tue Aug 20 22:12:19 CEST 2013
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)
More information about the Beginners
mailing list