haggle-0.1.0.0: A graph library offering mutable, immutable, and inductive graphs

Safe HaskellNone
LanguageHaskell2010

Data.Graph.Haggle

Contents

Description

Haggle is a Haskell graph library.

The main idea behind haggle is that graphs are constructed with mutation (either in IO or ST). After the graph is constructed, it is frozen into an immutable graph. This split is a major difference between haggle and the other major Haskell graph library, fgl, which is formulated in terms of inductive graphs that can always be modified in a purely-functional way. Supporting the inductive graph interface severely limits implementation choices and optimization opportunities, so haggle tries a different approach.

Furthermore, the types of vertices (nodes in FGL) and edges are held as abstract in haggle, allowing for changes later if necessary. That said, changes are unlikely and the representations are exposed (with no guarantees) through an Internal module.

Enough talk, example time:

import Control.Monad ( replicateM )
import Data.Graph.Haggle
import Data.Graph.Haggle.Digraph
import Data.Graph.Haggle.Algorithms.DFS

main :: IO ()
main = do
  g <- newMDigraph
  [v0, v1, v2] <- replicateM 3 (addVertex g)
  e1 <- addEdge g v0 v1
  e2 <- addEdge g v1 v2
  gi <- freeze g
  print (dfs gi v1) -- [V 1, V 2] since the first vertex is 0

The example builds a graph with three vertices and performs a DFS from the middle vertex. Note that the DFS algorithm is implemented on immutable graphs, so we freeze the mutable graph before traversing it. The graph type in this example is a directed graph.

There are other graph variants that support efficient access to predecessor edges: bidirectional graphs. There are also simple graph variants that prohibit parallel edges.

The core graph implementations support only vertices and edges. Adapters add support for Vertex and Edge labels. See EdgeLabelAdapter, VertexLabelAdapter, and LabelAdapter (which supports both). This split allows the core implementations of graphs and graph algorithms to be fast and compact (since they do not need to allocate storage for or manipulate labels). The adapters store labels on the side, similarly to the property maps of Boost Graph Library. Also note that the adapters are strongly typed. To add edges to a graph with edge labels, you must call addLabeledEdge instead of addEdge. Likewise for graphs with vertex labels and 'addLabeledVertex'/'addVertex'. This requirement is enforced in the type system so that labels cannot become out-of-sync with the structure of the graph. The adapters each work with any type of underlying graph.

Synopsis

Graph types

Mutable graphs

data MDigraph m Source #

This is a compact (mutable) directed graph.

newMDigraph :: (PrimMonad m, MonadRef m) => m (MDigraph m) Source #

Create a new empty mutable graph with a small amount of storage reserved for vertices and edges.

newSizedMDigraph :: (PrimMonad m, MonadRef m) => Int -> Int -> m (MDigraph m) Source #

Create a new empty graph with storage reserved for szVerts vertices and szEdges edges.

g <- newSizedMDigraph szVerts szEdges

data MBiDigraph m Source #

A mutable bidirectional graph

Instances
MBidirectional MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

MAddEdge MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Methods

addEdge :: (PrimMonad m, MonadRef m) => MBiDigraph m -> Vertex -> Vertex -> m (Maybe Edge) Source #

MAddVertex MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Methods

addVertex :: (PrimMonad m, MonadRef m) => MBiDigraph m -> m Vertex Source #

MGraph MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Associated Types

type ImmutableGraph MBiDigraph :: Type Source #

type ImmutableGraph MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

newMBiDigraph :: (PrimMonad m, MonadRef m) => m (MBiDigraph m) Source #

Allocate a new mutable bidirectional graph with a default size

newSizedMBiDigraph Source #

Arguments

:: (PrimMonad m, MonadRef m) 
=> Int

Reserved space for nodes

-> Int

Reserved space for edges

-> m (MBiDigraph m) 

Allocate a new mutable bidirectional graph with space reserved for nodes and edges. This can be more efficient and avoid resizing.

data MSimpleBiDigraph m Source #

Instances
MBidirectional MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

MAddEdge MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

MAddVertex MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

MGraph MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Associated Types

type ImmutableGraph MSimpleBiDigraph :: Type Source #

type ImmutableGraph MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Adapters

data EdgeLabeledMGraph g el s Source #

Instances
MBidirectional g => MBidirectional (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

MAddEdge g => MLabeledEdge (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type MEdgeLabel (EdgeLabeledMGraph g el) :: Type Source #

MAddVertex g => MAddVertex (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Methods

addVertex :: (PrimMonad m, MonadRef m) => EdgeLabeledMGraph g el m -> m Vertex Source #

MGraph g => MGraph (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type ImmutableGraph (EdgeLabeledMGraph g el) :: Type Source #

type MEdgeLabel (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

type MEdgeLabel (EdgeLabeledMGraph g el) = el
type ImmutableGraph (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

newEdgeLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => m (g m) -> m (EdgeLabeledMGraph g nl m) Source #

newSizedEdgeLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => (Int -> Int -> m (g m)) -> Int -> Int -> m (EdgeLabeledMGraph g el m) Source #

data VertexLabeledMGraph g nl m Source #

Instances
MBidirectional g => MBidirectional (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

MAddVertex g => MLabeledVertex (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type MVertexLabel (VertexLabeledMGraph g nl) :: Type Source #

MAddEdge g => MAddEdge (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Methods

addEdge :: (PrimMonad m, MonadRef m) => VertexLabeledMGraph g nl m -> Vertex -> Vertex -> m (Maybe Edge) Source #

MGraph g => MGraph (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type ImmutableGraph (VertexLabeledMGraph g nl) :: Type Source #

type MVertexLabel (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

type ImmutableGraph (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

newSizedVertexLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => (Int -> Int -> m (g m)) -> Int -> Int -> m (VertexLabeledMGraph g nl m) Source #

data LabeledMGraph g nl el m Source #

An adapter adding support for both vertex and edge labels for mutable graphs.

Instances
MBidirectional g => MBidirectional (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Methods

getPredecessors :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Vertex] Source #

getInEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Edge] Source #

MAddVertex g => MLabeledVertex (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type MVertexLabel (LabeledMGraph g nl el) :: Type Source #

MAddEdge g => MLabeledEdge (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type MEdgeLabel (LabeledMGraph g nl el) :: Type Source #

Methods

getEdgeLabel :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Edge -> m (Maybe (MEdgeLabel (LabeledMGraph g nl el))) Source #

unsafeGetEdgeLabel :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Edge -> m (MEdgeLabel (LabeledMGraph g nl el)) Source #

addLabeledEdge :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> Vertex -> MEdgeLabel (LabeledMGraph g nl el) -> m (Maybe Edge) Source #

MGraph g => MGraph (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type ImmutableGraph (LabeledMGraph g nl el) :: Type Source #

Methods

getVertices :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m [Vertex] Source #

getSuccessors :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Vertex] Source #

getOutEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Edge] Source #

countVertices :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m Int Source #

countEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m Int Source #

checkEdgeExists :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> Vertex -> m Bool Source #

freeze :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m (ImmutableGraph (LabeledMGraph g nl el)) Source #

type MVertexLabel (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type MVertexLabel (LabeledMGraph g nl el) = nl
type MEdgeLabel (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type MEdgeLabel (LabeledMGraph g nl el) = el
type ImmutableGraph (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

newLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => m (g m) -> m (LabeledMGraph g nl el m) Source #

newSizedLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => (Int -> Int -> m (g m)) -> Int -> Int -> m (LabeledMGraph g nl el m) Source #

Immutable graphs

data Digraph Source #

Instances
NFData Digraph Source #

The Digraph is always in normal form, as the vectors are all unboxed

Instance details

Defined in Data.Graph.Haggle.Digraph

Methods

rnf :: Digraph -> () #

Thawable Digraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Associated Types

type MutableGraph Digraph :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => Digraph -> m (MutableGraph Digraph m) Source #

Graph Digraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

type MutableGraph Digraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Adapters

data EdgeLabeledGraph g el Source #

Instances
(NFData g, NFData el) => NFData (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Methods

rnf :: EdgeLabeledGraph g el -> () #

Bidirectional g => BidirectionalEdgeLabel (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Graph g => HasEdgeLabel (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type EdgeLabel (EdgeLabeledGraph g el) :: Type Source #

Bidirectional g => Bidirectional (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Thawable g => Thawable (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type MutableGraph (EdgeLabeledGraph g el) :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => EdgeLabeledGraph g el -> m (MutableGraph (EdgeLabeledGraph g el) m) Source #

Graph g => Graph (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

type EdgeLabel (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

type EdgeLabel (EdgeLabeledGraph g el) = el
type MutableGraph (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

data VertexLabeledGraph g nl Source #

Instances
(NFData g, NFData nl) => NFData (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Methods

rnf :: VertexLabeledGraph g nl -> () #

Graph g => HasVertexLabel (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type VertexLabel (VertexLabeledGraph g nl) :: Type Source #

Bidirectional g => Bidirectional (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Thawable g => Thawable (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type MutableGraph (VertexLabeledGraph g nl) :: (Type -> Type) -> Type Source #

Graph g => Graph (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

type VertexLabel (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

type MutableGraph (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

fromEdgeList :: (MGraph g, MAddEdge g, MAddVertex g, Ord nl) => (forall s. ST s (g (ST s))) -> [(nl, nl)] -> (VertexLabeledGraph (ImmutableGraph g) nl, VertexMap nl) Source #

Build a new (immutable) graph from a list of edges. Edges are defined by pairs of node labels. A new Vertex will be allocated for each node label.

The type of the constructed graph is controlled by the first argument, which is a constructor for a mutable graph.

Example:

import Data.Graph.Haggle.VertexLabelAdapter
import Data.Graph.Haggle.SimpleBiDigraph

let g = fromEdgeList newMSimpleBiDigraph [(0,1), (1,2), (2,3), (3,0)]

g has type SimpleBiDigraph.

An alternative that is fully polymorphic in the return type would be possible, but it would require type annotations on the result of fromEdgeList, which could be very annoying.

data LabeledGraph g nl el Source #

An adapter adding support for both vertex and edge labels for immutable graphs.

Instances
(NFData g, NFData nl, NFData el) => NFData (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Methods

rnf :: LabeledGraph g nl el -> () #

Graph g => HasVertexLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type VertexLabel (LabeledGraph g nl el) :: Type Source #

Bidirectional g => BidirectionalEdgeLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Methods

labeledInEdges :: LabeledGraph g nl el -> Vertex -> [(Edge, EdgeLabel (LabeledGraph g nl el))] Source #

Graph g => HasEdgeLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type EdgeLabel (LabeledGraph g nl el) :: Type Source #

Bidirectional g => Bidirectional (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Methods

predecessors :: LabeledGraph g nl el -> Vertex -> [Vertex] Source #

inEdges :: LabeledGraph g nl el -> Vertex -> [Edge] Source #

Thawable g => Thawable (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type MutableGraph (LabeledGraph g nl el) :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => LabeledGraph g nl el -> m (MutableGraph (LabeledGraph g nl el) m) Source #

Graph g => Graph (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type VertexLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type VertexLabel (LabeledGraph g nl el) = nl
type EdgeLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type EdgeLabel (LabeledGraph g nl el) = el
type MutableGraph (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

fromLabeledEdgeList :: (Ord nl, MGraph g, MAddVertex g, MAddEdge g) => (forall s. ST s (g (ST s))) -> [(nl, nl, el)] -> (LabeledGraph (ImmutableGraph g) nl el, VertexMap nl) Source #

Construct a graph from a labeled list of edges. The node endpoint values are used as vertex labels, and the last element of the triple is used as an edge label.

Inductive graphs

data PatriciaTree nl el Source #

The PatriciaTree is a graph implementing the InductiveGraph interface (as well as the other immutable graph interfaces). It is based on the graph type provided by fgl.

Inductive graphs support more interesting decompositions than the other graph interfaces in this library, at the cost of less compact representations and some additional overhead on some operations, as most must go through the match operator.

This graph type is most useful for incremental construction in pure code. It also supports node removal from pure code.

Instances
(NFData nl, NFData el) => NFData (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Methods

rnf :: PatriciaTree nl el -> () #

InductiveGraph (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

HasVertexLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Associated Types

type VertexLabel (PatriciaTree nl el) :: Type Source #

BidirectionalEdgeLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

HasEdgeLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Associated Types

type EdgeLabel (PatriciaTree nl el) :: Type Source #

Bidirectional (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Graph (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

type VertexLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

type VertexLabel (PatriciaTree nl el) = nl
type EdgeLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

type EdgeLabel (PatriciaTree nl el) = el

Basic types

data Vertex Source #

An abstract representation of a vertex.

Note that the representation is currently exposed. Do not rely on this, as it is subject to change.

Instances
Eq Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

(==) :: Vertex -> Vertex -> Bool #

(/=) :: Vertex -> Vertex -> Bool #

Ord Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Show Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

NFData Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

rnf :: Vertex -> () #

Hashable Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

hashWithSalt :: Int -> Vertex -> Int #

hash :: Vertex -> Int #

data Edge Source #

An edge between two vertices.

Instances
Eq Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

(==) :: Edge -> Edge -> Bool #

(/=) :: Edge -> Edge -> Bool #

Ord Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

compare :: Edge -> Edge -> Ordering #

(<) :: Edge -> Edge -> Bool #

(<=) :: Edge -> Edge -> Bool #

(>) :: Edge -> Edge -> Bool #

(>=) :: Edge -> Edge -> Bool #

max :: Edge -> Edge -> Edge #

min :: Edge -> Edge -> Edge #

Show Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

NFData Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

rnf :: Edge -> () #

Hashable Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

hashWithSalt :: Int -> Edge -> Int #

hash :: Edge -> Int #

Mutable graph operations

getVertices :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m [Vertex] Source #

getSuccessors :: (MGraph g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Vertex] Source #

getOutEdges :: (MGraph g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Edge] Source #

countVertices :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m Int Source #

countEdges :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m Int Source #

freeze :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m (ImmutableGraph g) Source #

addEdge :: (MAddEdge g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m (Maybe Edge) Source #

removeVertex :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Vertex -> m () Source #

removeEdge :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Edge -> m () Source #

Mutable labeled graph operations

mapEdgeLabel :: LabeledGraph g nl el -> (el -> el') -> LabeledGraph g nl el' Source #

mapVertexLabel :: LabeledGraph g nl el -> (nl -> nl') -> LabeledGraph g nl' el Source #

Immutable graph operations

vertices :: Graph g => g -> [Vertex] Source #

edges :: Graph g => g -> [Edge] Source #

successors :: Graph g => g -> Vertex -> [Vertex] Source #

outEdges :: Graph g => g -> Vertex -> [Edge] Source #

edgesBetween :: Graph g => g -> Vertex -> Vertex -> [Edge] Source #

isEmpty :: Graph g => g -> Bool Source #

thaw :: (Thawable g, PrimMonad m, MonadRef m) => g -> m (MutableGraph g m) Source #

Inductive graph operations

data Context g Source #

Contexts represent the "context" of a Vertex, which includes the incoming edges of the Vertex, the label of the Vertex, and the outgoing edges of the Vertex.

Constructors

Context [(EdgeLabel g, Vertex)] (VertexLabel g) [(EdgeLabel g, Vertex)] 

Classes

These classes are a critical implementation detail, but are re-exported to simplify writing type signatures for generic functions.

class MGraph g Source #

The interface supported by a mutable graph.

Instances
MGraph MDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Associated Types

type ImmutableGraph MDigraph :: Type Source #

MGraph MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Associated Types

type ImmutableGraph MBiDigraph :: Type Source #

MGraph MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Associated Types

type ImmutableGraph MSimpleBiDigraph :: Type Source #

MGraph g => MGraph (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type ImmutableGraph (VertexLabeledMGraph g nl) :: Type Source #

MGraph g => MGraph (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type ImmutableGraph (EdgeLabeledMGraph g el) :: Type Source #

MGraph g => MGraph (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type ImmutableGraph (LabeledMGraph g nl el) :: Type Source #

Methods

getVertices :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m [Vertex] Source #

getSuccessors :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Vertex] Source #

getOutEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Edge] Source #

countVertices :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m Int Source #

countEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m Int Source #

checkEdgeExists :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> Vertex -> m Bool Source #

freeze :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m (ImmutableGraph (LabeledMGraph g nl el)) Source #

class MGraph g => MAddVertex g Source #

Minimal complete definition

addVertex

class MGraph g => MAddEdge g Source #

Minimal complete definition

addEdge

Instances
MAddEdge MDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Methods

addEdge :: (PrimMonad m, MonadRef m) => MDigraph m -> Vertex -> Vertex -> m (Maybe Edge) Source #

MAddEdge MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Methods

addEdge :: (PrimMonad m, MonadRef m) => MBiDigraph m -> Vertex -> Vertex -> m (Maybe Edge) Source #

MAddEdge MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

MAddEdge g => MAddEdge (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Methods

addEdge :: (PrimMonad m, MonadRef m) => VertexLabeledMGraph g nl m -> Vertex -> Vertex -> m (Maybe Edge) Source #

class MGraph g => MLabeledEdge g Source #

Minimal complete definition

unsafeGetEdgeLabel, addLabeledEdge

type family MEdgeLabel g Source #

Instances
type MEdgeLabel (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

type MEdgeLabel (EdgeLabeledMGraph g el) = el
type MEdgeLabel (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type MEdgeLabel (LabeledMGraph g nl el) = el

type family MVertexLabel g Source #

Instances
type MVertexLabel (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

type MVertexLabel (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type MVertexLabel (LabeledMGraph g nl el) = nl

class MGraph g => MRemovable g Source #

An interface for graphs that allow vertex and edge removal. Note that implementations are not required to reclaim storage from removed vertices (just make them inaccessible).

Minimal complete definition

removeVertex, removeEdgesBetween, removeEdge

class MGraph g => MBidirectional g Source #

An interface for graphs that support looking at predecessor (incoming edges) efficiently.

Minimal complete definition

getPredecessors, getInEdges

Instances
MBidirectional MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

MBidirectional MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

MBidirectional g => MBidirectional (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

MBidirectional g => MBidirectional (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

MBidirectional g => MBidirectional (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Methods

getPredecessors :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Vertex] Source #

getInEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Edge] Source #

class Graph g Source #

The basic interface of immutable graphs.

Minimal complete definition

vertices, edges, successors, outEdges, maxVertexId, isEmpty

Instances
Graph Digraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Graph BiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Graph SimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Graph (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Graph g => Graph (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Graph g => Graph (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Graph g => Graph (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

class Graph g => Thawable g Source #

Minimal complete definition

thaw

Instances
Thawable Digraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Associated Types

type MutableGraph Digraph :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => Digraph -> m (MutableGraph Digraph m) Source #

Thawable BiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Associated Types

type MutableGraph BiDigraph :: (Type -> Type) -> Type Source #

Thawable SimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Associated Types

type MutableGraph SimpleBiDigraph :: (Type -> Type) -> Type Source #

Thawable g => Thawable (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type MutableGraph (VertexLabeledGraph g nl) :: (Type -> Type) -> Type Source #

Thawable g => Thawable (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type MutableGraph (EdgeLabeledGraph g el) :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => EdgeLabeledGraph g el -> m (MutableGraph (EdgeLabeledGraph g el) m) Source #

Thawable g => Thawable (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type MutableGraph (LabeledGraph g nl el) :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => LabeledGraph g nl el -> m (MutableGraph (LabeledGraph g nl el) m) Source #

class Graph g => Bidirectional g Source #

The interface for immutable graphs with efficient access to incoming edges.

Minimal complete definition

predecessors, inEdges

class Graph g => HasEdgeLabel g Source #

The interface for immutable graphs with labeled edges.

Minimal complete definition

edgeLabel, labeledEdges

Instances
HasEdgeLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Associated Types

type EdgeLabel (PatriciaTree nl el) :: Type Source #

Graph g => HasEdgeLabel (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type EdgeLabel (EdgeLabeledGraph g el) :: Type Source #

Graph g => HasEdgeLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type EdgeLabel (LabeledGraph g nl el) :: Type Source #

type family EdgeLabel g Source #

Instances
type EdgeLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

type EdgeLabel (PatriciaTree nl el) = el
type EdgeLabel (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

type EdgeLabel (EdgeLabeledGraph g el) = el
type EdgeLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type EdgeLabel (LabeledGraph g nl el) = el

class Graph g => HasVertexLabel g Source #

The interface for immutable graphs with labeled vertices.

Minimal complete definition

vertexLabel, labeledVertices

type family VertexLabel g Source #

Instances
type VertexLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

type VertexLabel (PatriciaTree nl el) = nl
type VertexLabel (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

type VertexLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

type VertexLabel (LabeledGraph g nl el) = nl