Need help understanding (1) typeclass instances that have multiple parameter types, and (2) overlapping instances

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

On Jun 26, 2011, at 9:33 AM, Costello, Roger L. wrote:
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).
I'm not sure what you mean by "two parameter types" here. The instance has one parameter type: a pair of ints. ____________________ David Place Owner, Panpipes Ho! LLC http://panpipesho.com d@vidplace.com

On Sunday 26 June 2011, 15:33:45, Costello, Roger L. wrote:
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).
No, it also has only one parameter type, the type (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).
Int is a type constructor (of kind *), which is applied to 0 type variables [hence the type variables it is applied to are vacuously distinct]. (Int,Int) is the type constructor (,) applied to two type arguments [which are not type variables], both of which are the type Int. Haskell98 (probably also Haskell2010, I'm too lazy to look it up now) says all instance types must have the form (type constructor) applied to distinct type variables So instance (MyShow a, MyShow b) => MyShow (a,b) where ... is allowed, but none of instance (MyShow a) => MyShow (a,a) where ... (type variables not distinct) instance (MyShow a) => MyShow (a, Int) where .. (one non-type-variable) instance MyShow (Int,Int) where (two non-type-variables) instance Show a => MyShow a where ... (no type constructor)
Is that the rule?
Not quite, see above.
What is the rationale for that rule?
I'm not sure, I guess it's easier to implement.
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?
Yes, although in this case, it's rather "please lift an unnecessary and cumbersome restriction on the form of instance declarations".
There must be a good reason why Haskell prohibits non-variable types in multi-parameter instances.
Correcting the misunderstanding, it prohibits non-variable types as arguments to type constructors in instance heads, I know of no good reason why it does.
So there must be a downside to adding that pragma. What is the downside?
Your code will only work with implementations which have the FlexibleInstances extension.
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.
Type constructor (,) applied to two distinct type variables [a, b], that's the form allowed by H98.
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.
Exactly, the type (Int,Int) matches (a,b) as well as (Int,Int) [and it also matches (a,a), (Int,a), (a,Int)].
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?
That is what OverlappingInstances does, iirc; when several instance heads match, it chooses the most specific one if there is a well-defined most specific instance. If there is no well-defined most specific one, a compile error happens. But it's somewhat delicate, if you have a function foo :: (MyShow a) => a -> String and at some place you call it with an (Int,Int) argument, it may be that the compiler uses the general (a,b) instance and not the (Int,Int) one. Generally, OverlappingInstances are considered dangerous and if possible you should avoid them, and if you use them, you'd better know very well how instance selection happens. HTH, Daniel
participants (3)
-
Costello, Roger L.
-
Daniel Fischer
-
David Place