Trouble using MultiParamTypeClasses

I would be very grateful if someone could tell me what I'm doing wrong. Here's my code: ----- {-# LANGUAGE MultiParamTypeClasses #-} class Eq a => Graph g a where nodes :: g a -> [a] neighbours :: g a -> a -> [a] data WeightedGraph a w = WeightedGraph [(a, a, w)] instance Eq a => Graph a (WeightedGraph w a) where nodes = [] --stub neighbours = [] --stub ----- And here's the error message: temp.hs:9:24: Kind mis-match The first argument of `Graph' should have kind `* -> *', but `a' has kind `*' In the instance declaration for `Graph a (WeightedGraph w a)'

On Tuesday 22 November 2011, 13:41:11, Amy de Buitléir wrote:
I would be very grateful if someone could tell me what I'm doing wrong. Here's my code:
----- {-# LANGUAGE MultiParamTypeClasses #-}
class Eq a => Graph g a where nodes :: g a -> [a] neighbours :: g a -> a -> [a]
You apply `g' to the type `a', so `g' must be a type constructor taking one argument (because `g a' is a type). That means `g' must have the kind `* -> *' (the kind of type constructors taking one type as argument and producing a type).
data WeightedGraph a w = WeightedGraph [(a, a, w)]
WeightedGraph takes two type arguments (`a' and `w' must be types, since they're put in tuples) and constructs a type from them, so it has the kind * -> * -> *
instance Eq a => Graph a (WeightedGraph w a) where nodes = [] --stub neighbours = [] --stub
Since a is used as an argument to WeightedGraph, it must have kind *, but it is also used as the first parameter to the Graph class, which demands it has kind * -> *. Thus you have a kind mismatch. You have probably confused the order of parameters, so the WeightedGraph thing should be the first parameter and a the second. However, you mustn't provide WeightedGraph with all type arguments it takes, since the type expression you pass as first parameter to Graph must still take a type argument to produce a type. What you probably want is instance Eq a => Graph (WeightedGraph w) a where nodes _ = [] neighbours _ _ = []

Thank you, Daniel. That did the trick, and thanks to your explanation, I have a much better understanding of the syntax. In case anyone else has a similar problem, I also had to add the FlexibleInstances pragma.

I tried to make my previous example a bit more flexible, but I guess I was over-confident. Here's my code: ----- {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies, UndecidableInstances #-} class Eq a => Graph g a | g -> a where nodes :: g a -> [a] neighbours :: g a -> a -> [a] class (Graph g a, Eq a, Ord w) => WeightedGraph g w a | g -> w, g -> a where edges :: g w -> [(a, a, w)] data MyGraph w a = MyGraph [(a, a, w)] instance Eq a => Graph (MyGraph w) a where nodes _ = [] --stub neighbours _ _ = [] --stub instance (Graph g a, Eq a, Ord w) => WeightedGraph (MyGraph w a) where edges = [] -- stub ----- The error message is temp2.hs:16:53: Kind mis-match The first argument of `WeightedGraph' should have kind `* -> *', but `MyGraph w a' has kind `*' In the instance declaration for `WeightedGraph (MyGraph w a)' Failed, modules loaded: none. It seems to me that in the WeightedGraph class, g should have the kind * -> * -> *, and MyGraph has the kind * -> * -> *, so I'm not sure why I have a kind mismatch, but I suspect that I've written the instance declaration wrong. Any ideas how to fix it?
participants (2)
-
Amy de Buitléir
-
Daniel Fischer