
Hi all, I am not a Haskell expert, and I am currently exploring type classes and need some advice. I want to define a family of mutually recursive types as a collection of type classes and then I want to be able to map these collections of types to a set of other types using instance declarations. For example, I have a type family for graphs, consisting of the types "Node" and "Edge". In another part of my application I have the types "Person" and "Likes" (a pair of persons), and I want to map the roles "Node" and "Edge" to "Person" and "Likes", respectively. It seems to me that functional dependencies could be a way to model it (maybe it can also be done much simpler, but I don't know how). Here is what I tried: class (Node n, Edge e) => Graph g n e | g -> n, g -> e where class Node n where isConnectedTo :: Graph g n e => g -> n -> e -> Bool class Edge e where n1 :: Graph g n e => g -> e -> n n2 :: Graph g n e => g -> e -> n type Person = String type Likes = (Person, Person) data DummyGraph = DummyGraph String instance Graph DummyGraph Person Likes where instance Node Person where isConnectedTo g n (p1,p2) = (p1 == n) || (p2 == n) instance Edge Likes where n1 g (p1,p2) = p1 n2 g (p1,p2) = p2 This "DummyGraph" thing is supposed to be used as a kind of "family object" which stands for a particular type class family. However, this is not yet quite right because I get the error message Couldn't match the rigid variable `e' against `(a, b)' `e' is bound by the type signature for `isConnectedTo' Expected type: e Inferred type: (a, b) When checking the pattern: (p1, p2) In the definition of `isConnectedTo': isConnectedTo g n (p1, p2) = (p1 == n) || (p2 == n) Similar error messages occur in the instance declaration for Edge/Likes. I don't understand exactly what my error is. Maybe I would need a completely different strategy to model this. Any help would be appreciated! Regards, Klaus

On 11/6/05, Klaus Ostermann
instance Node Person where isConnectedTo g n (p1,p2) = (p1 == n) || (p2 == n)
At this point, isConnectedTo knows nothing about the third argument except that it is an edge, and there's no reason to think that an Edge is a tuple. All you can say is that there are two functions, n1 and n2, which extract the nodes of the edge. Use those instead, for example isConnectedTo g n p = n == n1 p || n == n2 p Couldn't match the rigid variable `e' against `(a, b)'
`e' is bound by the type signature for `isConnectedTo' Expected type: e Inferred type: (a, b) When checking the pattern: (p1, p2) In the definition of `isConnectedTo': isConnectedTo g n (p1, p2) = (p1 == n) || (p2 == n)
Hopefully this error makes more sense now. It's saying that it expected something of type 'e', but it found a tuple. regards, Fraser.

Hi Klaus, I think, for graphs at least, you should use a different approach. The function isConnectedTo only makes sense in the context of a graph, so class Node -- as it stands -- has no reason to be. Further, in your approach, you have the problem that instances of Edge are hard to define, because the Node-type can't be inferred (nothing prevents an instance Graph g' Int Likes, say with n1 g (p1,_) = length p1), so this won't compile, you must provide further information about the Node-type in the Edge class. It's fixable: class (Node n, Edge e n) => Graph g n e | g -> n, g -> e where class Node n where isConnectedTo :: Graph g n e => g -> n -> e -> Bool class Edge e n | e -> n where n1 :: Graph g n e => g -> e -> n n2 :: Graph g n e => g -> e -> n type Person = String type Likes = (Person, Person) data DummyGraph = DummyGraph String instance Graph DummyGraph Person Likes where instance Node Person where isConnectedTo g n e = n1 g e == n || n2 g e == n instance Edge Likes Person where n1 g (p1,p2) = p1 n2 g (p1,p2) = p2 But I don't like it. I'd prefer (very strongly) something like class Graph g n e | g -> n, g -> e where isConnectedTo :: g -> n -> e -> Bool -- or perhaps rather without "g" startNode, endNode :: e -> n . . . -- other Methods of interest like nodes, edges, components . . . with, e.g. instance Graph (Map node [node]) node (node,node) where . . . Cheers, Daniel Am Sonntag, 6. November 2005 15:01 schrieb Klaus Ostermann:
Hi all,
I am not a Haskell expert, and I am currently exploring type classes and need some advice.
I want to define a family of mutually recursive types as a collection of type classes and then I want to be able to map these collections of types to a set of other types using instance declarations.
For example, I have a type family for graphs, consisting of the types "Node" and "Edge". In another part of my application I have the types "Person" and "Likes" (a pair of persons), and I want to map the roles "Node" and "Edge" to "Person" and "Likes", respectively.
It seems to me that functional dependencies could be a way to model it (maybe it can also be done much simpler, but I don't know how).
Here is what I tried:
class (Node n, Edge e) => Graph g n e | g -> n, g -> e where
class Node n where isConnectedTo :: Graph g n e => g -> n -> e -> Bool
class Edge e where n1 :: Graph g n e => g -> e -> n n2 :: Graph g n e => g -> e -> n
type Person = String type Likes = (Person, Person)
data DummyGraph = DummyGraph String
instance Graph DummyGraph Person Likes where
instance Node Person where isConnectedTo g n (p1,p2) = (p1 == n) || (p2 == n)
instance Edge Likes where n1 g (p1,p2) = p1 n2 g (p1,p2) = p2
This "DummyGraph" thing is supposed to be used as a kind of "family object" which stands for a particular type class family. However, this is not yet quite right because I get the error message
Couldn't match the rigid variable `e' against `(a, b)' `e' is bound by the type signature for `isConnectedTo' Expected type: e Inferred type: (a, b) When checking the pattern: (p1, p2) In the definition of `isConnectedTo': isConnectedTo g n (p1, p2) = (p1 == n) || (p2 == n)
Similar error messages occur in the instance declaration for Edge/Likes.
I don't understand exactly what my error is. Maybe I would need a completely different strategy to model this.
Any help would be appreciated!
Regards, Klaus _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Daniel Fischer schrieb:
I'd prefer (very strongly) something like
class Graph g n e | g -> n, g -> e where isConnectedTo :: g -> n -> e -> Bool -- or perhaps rather without "g" startNode, endNode :: e -> n . . . -- other Methods of interest like nodes, edges, components . . .
with, e.g.
instance Graph (Map node [node]) node (node,node) where . . .
Thanks for the suggestion. This looks good, but it seems as if the "g" needs to occur in every signature, otherwise the interpreter throws a "No instance for ... arising from ..." error if you want to apply the function. Hence startNode would need to be startNode :: g -> e -> n rather than startNode :: e -> n Is there any way to get rid of this dummy argument? Klaus

Am Sonntag, 6. November 2005 17:30 schrieb Klaus Ostermann:
Daniel Fischer schrieb:
I'd prefer (very strongly) something like
class Graph g n e | g -> n, g -> e where isConnectedTo :: g -> n -> e -> Bool -- or perhaps rather without "g" startNode, endNode :: e -> n . . . -- other Methods of interest like nodes, edges, components . . .
with, e.g.
instance Graph (Map node [node]) node (node,node) where . . .
Thanks for the suggestion. This looks good, but it seems as if the "g" needs to occur in every signature, otherwise the interpreter throws a "No instance for ... arising from ..." error if you want to apply the function. Hence startNode would need to be startNode :: g -> e -> n rather than startNode :: e -> n
Is there any way to get rid of this dummy argument?
Klaus
Two I see, 1. retain class Edge, class Edge e n | e -> n, n -> e where isConnectedTo :: n -> e -> Bool startNode, endNode :: e -> n and then class (Edge e n) => Graph g n e | g -> n, g -> e where -- other methods if wanted 2. add more FunDeps, class Graph g n e | g -> n, g -> e, e -> n, n -> e, n e -> g where . . . works. Probably the second isn't wanted, because it introduces too much rigidity and an ADT might be better. Cheers, Daniel

Klaus Ostermann wrote:
I am not a Haskell expert, and I am currently exploring type classes and need some advice.
The most important advice is probably to point out that a `class' in Haskell is roughly comparable to an `interface' in Java, but not to a `class'.
class Node n where isConnectedTo :: Graph g n e => g -> n -> e -> Bool
This is not what you want. The type says: "Every node can find out whether it is connected to a given edge _in_any_type_of_graph_", which is clearly impossible given that your Graph class has no methods. Is your setting the notion of being a `Node' only makes sense in connection with a type of `Graph'. The right thing to so is probably to drop the classes `Edge' and `Node' and put their methods into the `Graph' class. class Graph g n e | g -> n e where isConnectedTo :: g -> n -> e -> Bool n1 :: g -> e -> n n2 :: g -> e -> n Udo.
participants (4)
-
Daniel Fischer
-
Fraser Wilson
-
Klaus Ostermann
-
Udo Stenzel