[Haskell-cafe] Families of type classes

Daniel Fischer daniel.is.fischer at web.de
Sun Nov 6 11:01:06 EST 2005


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list