dynamic-graphs-0.1.0.3: Dynamic graph algorithms

Safe HaskellNone
LanguageHaskell2010

Data.Graph.Dynamic.EulerTour

Contents

Description

This module provides dynamic connectivity for an acyclic graph (i.e. a forest).

It is based on: Finding biconnected components and computing tree functions in logarithmic parallel time by Robert E. Tarjan and Uzi Vishki (1984).

We use two naming conventions in this module:

  • A prime suffix (') indicates a simpler or less polymorphic version of a function or datatype. For example, see empty and empty', and Graph and Graph'.
  • An underscore suffix (_) means that the return value is ignored. For example, see link and link_.
Synopsis

Type

data Forest t a s v Source #

The most general type for an Euler Tour Forest. Used by other modules.

type Graph t s v = Forest t () s v Source #

Graph type polymorphic in the tree used to represent sequences.

type Graph' s v = Graph Tree s v Source #

Simple graph type.

Construction

empty :: forall t m v a. (Tree t, PrimMonad m) => (v -> v -> a) -> m (Forest t a (PrimState m) v) Source #

O(1)

Create the empty tree.

empty' :: PrimMonad m => m (Graph' (PrimState m) v) Source #

Simple version of empty.

edgeless :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => (v -> v -> a) -> [v] -> m (Forest t a (PrimState m) v) Source #

O(v*log(v))

Create a graph with the given vertices but no edges.

edgeless' :: (Eq v, Hashable v, PrimMonad m) => [v] -> m (Graph' (PrimState m) v) Source #

Simple version of edgeless.

fromTree :: forall v m t a. (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => (v -> v -> a) -> Tree v -> m (Forest t a (PrimState m) v) Source #

Create a graph from a Tree. Note that the values in nodes must be unique.

fromTree' :: (Eq v, Hashable v, PrimMonad m) => Tree v -> m (Graph' (PrimState m) v) Source #

Simple version of fromTree.

Queries

connected :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> v -> m Bool Source #

O(log(v))

Check if a path exists in between two vertices.

edge :: (Eq v, Hashable v, Tree t, PrimMonad m) => Forest t a (PrimState m) v -> v -> v -> m Bool Source #

O(log(v))

Check if this edge exists in the graph.

vertex :: (Eq v, Hashable v, Tree t, PrimMonad m) => Forest t a (PrimState m) v -> v -> m Bool Source #

O(log(v))

Check if this vertex exists in the graph.

neighbours :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> m [v] Source #

O(log(v) + n where n is the number of neighbours

Get all neighbours of the given vertex.

Modifying

link :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> v -> m Bool Source #

O(log(v))

Insert an edge in between two vertices. If the vertices are already connected, we don't do anything, since this is an acyclic graph. Returns whether or not an edge was actually inserted.

link_ :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> v -> m () Source #

Version of link which ignores the result.

cut :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> v -> m Bool Source #

O(log(v))

Remove an edge in between two vertices. If there is no edge in between these vertices, do nothing. Return whether or not an edge was actually removed.

cut_ :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> v -> m () Source #

Version of cut which ignores the result.

insert :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> m Bool Source #

O(log(v))

Insert a new vertex. Do nothing if it is already there. Returns whether or not a vertex was inserted in the graph.

insert_ :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> m () Source #

Version of insert which ignores the result.

delete :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> m Bool Source #

O(n*log(v)) where n is the number of neighbours

Remove a vertex from the graph, if it exists. If it is connected to any other vertices, those edges are cut first. Returns whether or not a vertex was removed from the graph.

delete_ :: (Eq v, Hashable v, Tree t, PrimMonad m, Monoid a) => Forest t a (PrimState m) v -> v -> m () Source #

Version of delete which ignores the result.

Advanced/internal operations

findRoot :: (Eq v, Hashable v, Tree t, PrimMonad m, s ~ PrimState m, Monoid a) => Forest t a s v -> v -> m (Maybe (t s (v, v) a)) Source #

componentSize :: (Eq v, Hashable v, Tree t, PrimMonad m, s ~ PrimState m) => Forest t (Sum Int) s v -> v -> m Int Source #

spanningForest :: (Eq v, Hashable v, Tree t, Monoid a, PrimMonad m) => Forest t a (PrimState m) v -> m (Forest v) Source #

Obtain the current spanning forest.

Debugging

print :: (Show a, Monoid b, TestTree t) => Forest t b RealWorld a -> IO () Source #