Here's a type for cyclic, directed graphs with labelled nodes and edges.
import qualified Data.Map as M
import Data.Foldable
import Data.Monoid
data Node n e = N n [(e, Node n e)] -- the node's label and its list of neighbors
newtype Graph n e = G (M.Map n (Node n e))
To handle the case where the graph has a loop, it's possible to 'tie the knot' and create infinitely recursive graphs in finite space.
type GraphInput n e = M.Map n [(e, n)]
mkGraph :: Ord n => GraphInput n e -> Graph n e
mkGraph spec = G $ nodeMap
where nodeMap = M.mapWithKey mkNode (makeConsistent spec)
-- mkNode :: n -> [(e, n)] -> Node n e
mkNode lbl edges = N lbl $ map getEdge edges
-- We know that (!) can't fail because we ensured that
-- all edges have a key in the map (see makeConsistent)
getEdge (e, lbl) = (e, nodeMap ! lbl)
makeConsistent :: Ord n => GraphInput n e -> GraphInput n e
makeConsistent m = foldr addMissing m nodesLinkedTo
where addMissing el m = M.insertWith (\_ old -> old) el [] m
nodesLinkedTo = map snd $ join $ M.elems m
By viewing the graph as a collection of nodes, we can write a Foldable
instance which performs a depth-first traversal.*
newtype NodeGraph e n = NG {getNodeGraph :: Graph n e}
instance Foldable (NodeGraph e) where
foldMap f (NG (G m)) = foldMap mapNode (M.elems m)
where mapNode (N n es) = f n `mappend` foldMap mapEdge es
mapEdge (e, n) = mapNode n
However, even for simple tree-shaped graphs, this produces duplicate elements:
-- A
-- / \ X
-- B C
-- |
-- D
ghci> let ng = NG $ mkGraph [('A', [(1, 'B'), (1, 'C')]), ('C', [(1, 'D')]), ('X', [])]
ghci> let toList = Data.Foldable.foldr (:) []
ghci> toList ng
"ABCDBCDDX"
When the graph has a cycle, the effect is even more dramatic - foldMap
recurses forever! The items in the loop are repeated, and some elements are never returned!
Is this okay? Can a instance of Foldable
return some of its elements more than once, or am I violating the contract of the class? Can an instance loop on a part of the structure infinitely? I've been looking for guidance on this issue - I was hoping for a set of 'Foldable laws' that would settle the question - but I haven't been able to find any discussion of the question online.
One approach to get out of this would be to 'remember' the elements which have already been visited as I traverse the graph. However, this would add an Eq
or Ord
constraint to the signature of foldMap
, which precludes my type being a member of Foldable
.
* Incidentally, we can't write a Functor
instance for NodeGraph
, because it would break the invariant that nodes in a graph are uniquely labelled. (fmap (const "foo")
, for example, will relabel every node to "foo", though they'll all have different sets of edges!) We can (with the appropriate newtype
) write a Functor
which maps all the edge labels, though.
There are currently very few Foldable
laws, so you can do all sorts of things. In fact, there are several different Foldable
instances you could write, corresponding to different traversal orders. The Foldable
laws describe relationships among the different Foldable
members and, if the type is also a Functor
, an additional law relating fold
, foldMap
, and fmap
.
Some specifics: There are straightforward "laws" about the relationships between foldMap
, foldl
, foldr
, sum
, etc., which just say that they should act pretty much like their default implementations except for strictness. For fold
, this law is fold = foldMap id
. If the container is also a Functor
, there's a law specifying that you can go the other way: foldMap f = fold . fmap f
. Nothing too exciting at all, as I said.
On the other hand, I think trying to combine knot-tying with unique labeling smells a bit funny. I'm not sure what you're up to with that, or whether it really makes sense. The trouble, as I see it, is that although sharing leads to the graph being represented in memory as you want, this sharing is not reflected in the language at all. Within Haskell, a graph with cycles looks exactly like an infinite tree. There is, in fact, very little you can do with a cyclic graph that won't (potentially) turn it into an infinite tree. This is why people bother using things like Data.Map
to represent graphs in the first place—knot tying doesn't offer a clear view of the graph structure.