newbie : multi-parameter type classes

Hi there. I'm trying to define a generic graph type here and don't understand on one error I get. Here I come. module Graph where class (Eq n, Eq e) => Topo a n e where empty :: a nodes :: a -> [n] edges :: a -> [e] data Node n = Node n deriving (Eq,Show) data Edge n e = Edge e (Node n) (Node n) deriving (Show) instance (Eq e) => Eq (Edge n e) where (Edge e1 _ _) == (Edge e2 _ _) = e1 == e2 data Graph n e = Graph [Node n] [Edge n e] deriving (Eq,Show) instance (Eq n, Eq e) => Topo (Graph n e) (Node n) (Edge n e) where empty = Graph [] [] nodes (Graph ns _) = ns edges (Graph _ es) = es My class Topo (for topography) is supposed to give the basic interface any graph should have. My instance is Topo (Graph n e) (Node n) (Edge n e), so the infered types of the functions should be : empty :: Graph n e nodes :: Graph n e -> [Nodes n] edges :: Graph n e -> [Edge n e] right ? When I load the code in GHCi, no errors. But then : *Graph> let g = Graph [Node 0, Node 1] [] *Graph> nodes g <interactive>:1:0: No instance for (Topo (Graph Integer e1) n e) arising from use of `nodes' at <interactive>:1:0-6 Possible fix: add an instance declaration for (Topo (Graph Integer e1) n e) In the expression: nodes g In the definition of `it': it = nodes g *Graph> And I don't understand this. How can he search for an instance of Topo (Graph integer e1) n e) ? regards, Thomas

Thomas Girod wrote:
Hi there.
I'm trying to define a generic graph type here and don't understand on one error I get. Here I come.
module Graph where
class (Eq n, Eq e) => Topo a n e where empty :: a nodes :: a -> [n] edges :: a -> [e]
This does not work without functional dependencies. Try: class (Eq n, Eq e) => Topo a n e | a -> n e where HTH Christian P.S. Integer comes in via defaulting (of 0 or 1)

Thomas Girod wrote:
class (Eq n, Eq e) => Topo a n e where empty :: a
empty does not allow to infer the types n and e
nodes :: a -> [n]
also nodes leaves the type e undetermined http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html... Unfortunately http://www.cse.ogi.edu/~mpj/pubs/fundeps.html is broken. Christian

Unfortunately http://www.cse.ogi.edu/~mpj/pubs/fundeps.html is broken.
participants (3)
-
Christian Maeder
-
Matthew Brecknell
-
Thomas Girod