impure-containers-0.5.1: Mutable containers in Haskell.

Safe HaskellNone
LanguageHaskell2010

Data.Graph.Immutable

Contents

Description

This module provides a safe and performant way to perform operations on graphs. The types Graph, Vertex, Vertices and Size are all parameterized by a phantom type variable g. Much like the s used with ST, this type variable will always be free. It gives us a guarentee that a vertex belongs in a graph. See the bottom of this page for a more detailed explanation.

Synopsis

Graph Operations

lookupVertex :: Eq v => v -> Graph g e v -> Maybe (Vertex g) Source #

Lookup a Vertex by its label.

lookupEdge :: Vertex g -> Vertex g -> Graph g e v -> Maybe e Source #

atVertex :: Vertex g -> Graph g e v -> v Source #

mapVertices :: (Vertex g -> a -> b) -> Graph g e a -> Graph g e b Source #

Not the same as fmap because the function also takes the vertex id.

mapEdges :: (Vertex g -> Vertex g -> e -> d) -> Graph g e v -> Graph g d v Source #

Map of the edges in the graph.

traverseVertices_ :: Applicative m => (Vertex g -> v -> m a) -> Graph g e v -> m () Source #

traverseEdges_ :: Applicative m => (Vertex g -> Vertex g -> v -> v -> e -> m a) -> Graph g e v -> m () Source #

This traverses every edge in the entire graph.

traverseNeighbors_ :: Applicative m => (Vertex g -> v -> e -> m a) -> Vertex g -> Graph g e v -> m () Source #

Traverse the neighbors of a specific vertex.

vertices :: Graph g e v -> Vertices g v Source #

Get the vertices from a graph.

setVertices :: Vertices g v -> Graph g e w -> Graph g e v Source #

Set the vertices of a graph.

size :: Graph g e v -> Size g Source #

Get the number of vertices in a graph.

freeze :: PrimMonad m => MGraph (PrimState m) g e v -> m (Graph g e v) Source #

Make an immutable copy of a mutable graph.

create :: PrimMonad m => (forall g. MGraph (PrimState m) g e v -> m ()) -> m (SomeGraph e v) Source #

Takes a function that builds on an empty MGraph. After the function mutates the MGraph, it is frozen and becomes an immutable SomeGraph.

with :: SomeGraph e v -> (forall g. Graph g e v -> a) -> a Source #

Take a function that can be performed on any Graph and perform that on the given SomeGraph.

mapSome :: (forall g. Graph g e v -> Graph g e' v') -> SomeGraph e v -> SomeGraph e' v' Source #

Lift a Graph morphism into a SomeGraph morphism.

Algorithms

dijkstra Source #

Arguments

:: (Ord s, Monoid s, Foldable t) 
=> (v -> v -> s -> e -> s)

Weight function

-> s

Weight to assign start vertex

-> t (Vertex g)

Start vertices

-> Graph g e v

Graph

-> Graph g e s 

This is a generalization of Dijkstra's algorithm. Like the original, it takes a start Vertex but unlike the original, it does not take an end. It will continue traversing the Graph until it has touched all vertices that are reachable from the start vertex.

Additionally, this function generalizes the notion of distance. It can be numeric (as Dijkstra has it) data, non-numeric data, or tagged numeric data. This can be used, for example, to find the shortest path from the start vertex to all other vertices in the graph.

In Dijkstra's original algorithm, tentative distances are initialized to infinity. After a node is visited, the procedure for updating its neighbors' tentative distance to a node is to compare the existing tentative distance with the new one and to keep the lesser of the two.

In this variant, tentative distances are initialized to mempty. The update procedure involves combining them with mappend instead of being choosing the smaller of the two. For this algorithm to function correctly, the distance s must have Ord and Monoid instances satisfying:

∀ a b. mappend a b ≤ a
∀ a b. mappend a b ≤ b
∀ c.   mempty ≥ c

Additionally, the Monoid instance should have a commutative mappend:

∀ a b. mappend a b ≅ mappend b a

The weight function is described by:

from    to    from   edge   tentative
node   node  weight  value  to weight
 |      |      |      |      |
 V      V      V      V      V

(v  ->  v  ->  s  ->  e  ->  s)

In many cases, some of input values can be ignored. For example, to implement Dijkstra's original algorithm the from-node and to-node values are not needed. The weight combining function will typically use the from-weight in some way. The way this algorithm uses the weight function makes it suseptible to the same negative-edge problem as the original. For some weight combining function f, it should be the case that:

∀ v1 v2 s e. f v1 v2 s e ≥ s

This function could be written without unsafely pattern matching on Vertex, but doing so allows us to use a faster heap implementation.

dijkstraDistance Source #

Arguments

:: (Num e, Ord e) 
=> Vertex g

Start vertex

-> Vertex g

End vertex

-> Graph g e v

Graph

-> Maybe e 

Find the shortest path between two vertices using Dijkstra's algorithm. The source code of this function provides an example of how to use the generalized variants of Dijkstra's algorithm provided by this module.

dijkstraFoldM Source #

Arguments

:: (Ord s, Monoid s, Foldable t, PrimMonad m) 
=> (v -> v -> s -> e -> s)

Weight function

-> (v -> s -> x -> m x)

Monadic fold function

-> s

Weight to assign start vertex

-> x

Initial accumulator

-> t (Vertex g)

Start vertices

-> Graph g e v

Graph

-> m x 

Size and Vertex

vertexInt :: Vertex g -> Int Source #

Convert a Vertex to an Int.

Vertices

verticesTraverse :: Applicative m => (Vertex g -> v -> m a) -> Vertices g v -> m (Vertices g a) Source #

This is currently inefficient. If an itraverse gets added to vector, this can be made faster.

verticesTraverse_ :: Applicative m => (Vertex g -> v -> m a) -> Vertices g v -> m () Source #

This is currently inefficient. If an itraverse gets added to vector, this can be made faster.

verticesThaw :: PrimMonad m => Vertices g v -> m (MVertices (PrimState m) g v) Source #

Make a mutable copy of a set of Vertices.