graphs: A simple monadic graph library

[ algorithms, bsd3, data-structures, graphs, library ] [ Propose Tags ]

A "not-very-Haskelly" API for calculating traversals of graphs that may be too large to fit into memory. The algorithms included are inspired by the visitor concept of the Boost Graph Library.

Here is a very simple example of how we might execute a depth-first-search. In this case the visitor simply collects the edges and vertices in the order that the corresponding functions get called. After the necessary imports,

import Data.Array
import Data.Monoid
import Data.Graph.AdjacencyList
import Data.Graph.Algorithm
import Data.Graph.Algorithm.DepthFirstSearch

create an adjacency list where the vertices are labeled with integers.

graph :: Array Int [Int]
graph = array (0, 3) [(0, [1,2]), (1, [3]), (2, [3]), (3, [])]

We need a data structure that instantiates Monoid to combine the results of our visitor functions.

data Orderings = Orderings
  {  enterV :: [Int]
  ,  enterE :: [(Int, Int)]
  ,  gray   :: [(Int, Int)]
  ,  exitV  :: [Int]
  ,  black  :: [(Int, Int)]
  } deriving Show

instance Monoid Orderings where
 mempty = Orderings [] [] [] [] []
 mappend (Orderings a1 a2 a3 a4 a5)(Orderings b1 b2 b3 b4 b5) =
  Orderings (a1 ++ b1) (a2 ++ b2) (a3 ++ b3) (a4 ++ b4) (a5 ++ b5)

The dfs function's first argument is of type GraphSearch which is a visitor containing the functions to be run at various times during the search. The second argument is the starting vertex for the search.

orderings :: GraphSearch (AdjacencyList Int) Orderings
orderings = GraphSearch
  (\v -> return $ mempty {enterV = [v]})
  (\e -> return $ mempty {enterE = [e]})
  (\e -> return $ mempty {gray   = [e]})
  (\v -> return $ mempty {exitV  = [v]})
  (\e -> return $ mempty {black  = [e]})

Finally runAdjacencylist unwraps the function in the Adjacencylist newtype and runs it on graph.

dfsTest :: Orderings
dfsTest = runAdjacencyList (dfs orderings 0) graph

Running dfsTest in ghci will yield:

Orderings {enterV = [0,2,3,1], enterE = [(0,2),(2,3),(0,1)], gray = [], exitV = [3,2,1,0], black = [(1,3)]}

[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1, 0.2, 0.3, 0.3.1, 0.3.2, 0.3.2.1, 0.3.2.2, 0.3.2.3, 0.4, 0.4.0.1, 0.4.0.3, 0.4.1, 0.5, 0.5.0.1, 0.6, 0.6.0.1, 0.7, 0.7.1, 0.7.2
Change log CHANGELOG.markdown
Dependencies array (>=0.3 && <0.7), base (>=4 && <5), containers (>=0.3 && <0.8), semigroups (>=0.16 && <1), transformers (>=0.2.2 && <0.7), transformers-compat (>=0.3 && <1), void (>=0.5.5.1 && <1) [details]
License BSD-3-Clause
Copyright Copyright (C) 2011-2013 Edward A. Kmett
Author Edward A. Kmett
Maintainer Edward A. Kmett <ekmett@gmail.com>
Revised Revision 1 made by ryanglscott at 2023-09-30T13:11:27Z
Category Algorithms, Data Structures, Graphs
Home page http://github.com/ekmett/graphs
Bug tracker http://github.com/ekmett/graphs/issues
Source repo head: git clone git://github.com/ekmett/graphs.git
Uploaded by ryanglscott at 2022-05-07T23:42:40Z
Distributions LTSHaskell:0.7.2, NixOS:0.7.2, Stackage:0.7.2
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 14487 total (45 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2022-05-08 [all 1 reports]

Readme for graphs-0.7.2

[back to package description]

graphs

Hackage Build Status

This provides a "not-very-Haskelly" API for calculating traversals of graphs that may be too large to fit into memory.

Contact Information

Contributions and bug reports are welcome!

Please feel free to contact me through github or on the #haskell IRC channel on irc.freenode.net.

-Edward Kmett