[Haskell-beginners] Need help understanding (1) typeclass instances that have multiple parameter types, and (2) overlapping instances
Costello, Roger L.
costello at mitre.org
Sun Jun 26 15:33:45 CEST 2011
Hi Folks,
I have questions about:
- typeclass instances that have multiple parameter types
- overlapping instances
Let's take an example of a typeclass with two instances:
class MyShow a where
toString :: a -> String
instance MyShow Int where
toString = show
instance MyShow (Int, Int) where
toString (a, b) = toString a ++ ", " ++ toString b
The first instance has one parameter type (Int) and the second instance has two parameter types (Int, Int).
When the class and instances are compiled, this error is generated:
Illegal instance declaration for `MyShow (Int, Int)'
(All instance types must be of the form (T a1 ... an)
where a1 ... an are type *variables*,
and each type variable appears at most once in the instance head.
Use -XFlexibleInstances if you want to disable this.)
In the instance declaration for `MyShow (Int, Int)'
I interpret that error message to mean that Haskell has this rule:
Instances with one parameter type can specify non-variable
types (such as Int), but instances with multiple parameter
types can only use variable types (e.g., a, b, c).
Is that the rule?
What is the rationale for that rule?
Next, I placed this at the top of my file:
{-# LANGUAGE FlexibleInstances #-}
and the error message went away.
Apparently the pragma is telling the compiler:
Even though the Haskell code does not strictly conform to the
Haskell specification, please let it compile.
Is that what the pragma is telling the compiler?
There must be a good reason why Haskell prohibits non-variable types in multi-parameter instances. So there must be a downside to adding that pragma. What is the downside?
Now let's move on to my questions about overlapping instances.
I created a third instance. It is for a pair of values of any type:
instance (MyShow a, MyShow b) => MyShow (a, b) where
toString (a, b) = ">>" ++ toString a ++ " " ++ toString b ++ "<<"
It compiles without error.
But if I try to use the second instance (the one that was defined for two Int's):
toString ((34 :: Int), (44 :: Int))
then I get an overlapping instances error:
Overlapping instances for MyShow (Int, Int)
arising from a use of `toString'
Matching instances:
instance MyShow (Int, Int) -- Defined at Overlap.hs:11:9-25
instance (MyShow a, MyShow b) => MyShow (a, b)
In the expression: toString ((34 :: Int), (44 :: Int))
I see how this:
toString ((34 :: Int), (44 :: Int))
can match with the second and third instances, and thus the compiler has ambiguity on which instance to use.
Is there a way to express,
Hey compiler, please use this instance:
instance MyShow (Int, Int)
That is, when confronted with overlapping instances, what should I do?
/Roger
More information about the Beginners
mailing list