
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 _ _ = []