Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data MDigraph m
- newMDigraph :: (PrimMonad m, MonadRef m) => m (MDigraph m)
- newSizedMDigraph :: (PrimMonad m, MonadRef m) => Int -> Int -> m (MDigraph m)
- data MBiDigraph m
- newMBiDigraph :: (PrimMonad m, MonadRef m) => m (MBiDigraph m)
- newSizedMBiDigraph :: (PrimMonad m, MonadRef m) => Int -> Int -> m (MBiDigraph m)
- data MSimpleBiDigraph m
- newMSimpleBiDigraph :: (PrimMonad m, MonadRef m) => m (MSimpleBiDigraph m)
- newSizedMSimpleBiDigraph :: (PrimMonad m, MonadRef m) => Int -> Int -> m (MSimpleBiDigraph m)
- data EdgeLabeledMGraph g el s
- newEdgeLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => m (g m) -> m (EdgeLabeledMGraph g nl m)
- newSizedEdgeLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => (Int -> Int -> m (g m)) -> Int -> Int -> m (EdgeLabeledMGraph g el m)
- data VertexLabeledMGraph g nl m
- newVertexLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => m (g m) -> m (VertexLabeledMGraph g nl m)
- newSizedVertexLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => (Int -> Int -> m (g m)) -> Int -> Int -> m (VertexLabeledMGraph g nl m)
- data LabeledMGraph g nl el m
- newLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => m (g m) -> m (LabeledMGraph g nl el m)
- newSizedLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => (Int -> Int -> m (g m)) -> Int -> Int -> m (LabeledMGraph g nl el m)
- data Digraph
- data BiDigraph
- data SimpleBiDigraph
- data EdgeLabeledGraph g el
- data VertexLabeledGraph g nl
- fromEdgeList :: (MGraph g, MAddEdge g, MAddVertex g, Ord nl) => (forall s. ST s (g (ST s))) -> [(nl, nl)] -> (VertexLabeledGraph (ImmutableGraph g) nl, VertexMap nl)
- data LabeledGraph g nl el
- 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)
- data PatriciaTree nl el
- data Vertex
- data Edge
- edgeSource :: Edge -> Vertex
- edgeDest :: Edge -> Vertex
- getVertices :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m [Vertex]
- getSuccessors :: (MGraph g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Vertex]
- getOutEdges :: (MGraph g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Edge]
- countVertices :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m Int
- countEdges :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m Int
- checkEdgeExists :: (MGraph g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m Bool
- freeze :: (MGraph g, PrimMonad m, MonadRef m) => g m -> m (ImmutableGraph g)
- addVertex :: (MAddVertex g, PrimMonad m, MonadRef m) => g m -> m Vertex
- addEdge :: (MAddEdge g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m (Maybe Edge)
- getEdgeLabel :: (MLabeledEdge g, PrimMonad m, MonadRef m) => g m -> Edge -> m (Maybe (MEdgeLabel g))
- unsafeGetEdgeLabel :: (MLabeledEdge g, PrimMonad m, MonadRef m) => g m -> Edge -> m (MEdgeLabel g)
- addLabeledEdge :: (MLabeledEdge g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> MEdgeLabel g -> m (Maybe Edge)
- getVertexLabel :: (MLabeledVertex g, PrimMonad m, MonadRef m) => g m -> Vertex -> m (Maybe (MVertexLabel g))
- addLabeledVertex :: (MLabeledVertex g, PrimMonad m, MonadRef m) => g m -> MVertexLabel g -> m Vertex
- getLabeledVertices :: (MLabeledVertex g, PrimMonad m, MonadRef m) => g m -> m [(Vertex, MVertexLabel g)]
- removeVertex :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Vertex -> m ()
- removeEdgesBetween :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m ()
- removeEdge :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Edge -> m ()
- getPredecessors :: (MBidirectional g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Vertex]
- getInEdges :: (MBidirectional g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Edge]
- mapEdgeLabel :: LabeledGraph g nl el -> (el -> el') -> LabeledGraph g nl el'
- mapVertexLabel :: LabeledGraph g nl el -> (nl -> nl') -> LabeledGraph g nl' el
- vertices :: Graph g => g -> [Vertex]
- edges :: Graph g => g -> [Edge]
- successors :: Graph g => g -> Vertex -> [Vertex]
- outEdges :: Graph g => g -> Vertex -> [Edge]
- edgesBetween :: Graph g => g -> Vertex -> Vertex -> [Edge]
- edgeExists :: Graph g => g -> Vertex -> Vertex -> Bool
- isEmpty :: Graph g => g -> Bool
- thaw :: (Thawable g, PrimMonad m, MonadRef m) => g -> m (MutableGraph g m)
- predecessors :: Bidirectional g => g -> Vertex -> [Vertex]
- inEdges :: Bidirectional g => g -> Vertex -> [Edge]
- edgeLabel :: HasEdgeLabel g => g -> Edge -> Maybe (EdgeLabel g)
- labeledEdges :: HasEdgeLabel g => g -> [(Edge, EdgeLabel g)]
- labeledOutEdges :: HasEdgeLabel g => g -> Vertex -> [(Edge, EdgeLabel g)]
- vertexLabel :: HasVertexLabel g => g -> Vertex -> Maybe (VertexLabel g)
- labeledVertices :: HasVertexLabel g => g -> [(Vertex, VertexLabel g)]
- labeledInEdges :: BidirectionalEdgeLabel g => g -> Vertex -> [(Edge, EdgeLabel g)]
- emptyGraph :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g
- match :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Maybe (Context g, g)
- context :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Maybe (Context g)
- insertLabeledVertex :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> VertexLabel g -> (Vertex, g)
- insertLabeledEdge :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Vertex -> EdgeLabel g -> Maybe (Edge, g)
- deleteEdge :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Edge -> g
- deleteEdgesBetween :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Vertex -> g
- replaceLabeledEdge :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Vertex -> EdgeLabel g -> Maybe (Edge, g)
- deleteVertex :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> g
- data Context g = Context [(EdgeLabel g, Vertex)] (VertexLabel g) [(EdgeLabel g, Vertex)]
- class MGraph g
- type family ImmutableGraph g
- class MGraph g => MAddVertex g
- class MGraph g => MAddEdge g
- class MGraph g => MLabeledEdge g
- type family MEdgeLabel g
- class MGraph g => MLabeledVertex g
- type family MVertexLabel g
- class MGraph g => MRemovable g
- class MGraph g => MBidirectional g
- class Graph g
- class Graph g => Thawable g
- type family MutableGraph g :: (* -> *) -> *
- class Graph g => Bidirectional g
- class Graph g => HasEdgeLabel g
- type family EdgeLabel g
- class Graph g => HasVertexLabel g
- type family VertexLabel g
- class (HasEdgeLabel g, Bidirectional g) => BidirectionalEdgeLabel g
- class (Graph g, HasEdgeLabel g, HasVertexLabel g) => InductiveGraph g
Graph types
Mutable graphs
This is a compact (mutable) directed graph.
Instances
MAddEdge MDigraph Source # | |
MAddVertex MDigraph Source # | |
MGraph MDigraph Source # | |
Defined in Data.Graph.Haggle.Digraph type ImmutableGraph MDigraph :: Type Source # getVertices :: (PrimMonad m, MonadRef m) => MDigraph m -> m [Vertex] Source # getSuccessors :: (PrimMonad m, MonadRef m) => MDigraph m -> Vertex -> m [Vertex] Source # getOutEdges :: (PrimMonad m, MonadRef m) => MDigraph m -> Vertex -> m [Edge] Source # countVertices :: (PrimMonad m, MonadRef m) => MDigraph m -> m Int Source # countEdges :: (PrimMonad m, MonadRef m) => MDigraph m -> m Int Source # checkEdgeExists :: (PrimMonad m, MonadRef m) => MDigraph m -> Vertex -> Vertex -> m Bool Source # freeze :: (PrimMonad m, MonadRef m) => MDigraph m -> m (ImmutableGraph MDigraph) Source # | |
type ImmutableGraph MDigraph Source # | |
Defined in Data.Graph.Haggle.Digraph |
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
newMBiDigraph :: (PrimMonad m, MonadRef m) => m (MBiDigraph m) Source #
Allocate a new mutable bidirectional graph with a default size
:: (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
newMSimpleBiDigraph :: (PrimMonad m, MonadRef m) => m (MSimpleBiDigraph m) Source #
newSizedMSimpleBiDigraph :: (PrimMonad m, MonadRef m) => Int -> Int -> m (MSimpleBiDigraph m) Source #
Adapters
data EdgeLabeledMGraph g el s Source #
Instances
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
newVertexLabeledGraph :: (MGraph g, PrimMonad m, MonadRef m) => m (g m) -> m (VertexLabeledMGraph g nl m) Source #
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
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
Instances
NFData Digraph Source # | The |
Defined in Data.Graph.Haggle.Digraph | |
Thawable Digraph Source # | |
Graph Digraph Source # | |
Defined in Data.Graph.Haggle.Digraph vertices :: Digraph -> [Vertex] Source # edges :: Digraph -> [Edge] Source # successors :: Digraph -> Vertex -> [Vertex] Source # outEdges :: Digraph -> Vertex -> [Edge] Source # maxVertexId :: Digraph -> Int Source # isEmpty :: Digraph -> Bool Source # edgesBetween :: Digraph -> Vertex -> Vertex -> [Edge] Source # | |
type MutableGraph Digraph Source # | |
Defined in Data.Graph.Haggle.Digraph |
An immutable bidirectional graph
Instances
Bidirectional BiDigraph Source # | |
Thawable BiDigraph Source # | |
Graph BiDigraph Source # | |
Defined in Data.Graph.Haggle.BiDigraph vertices :: BiDigraph -> [Vertex] Source # edges :: BiDigraph -> [Edge] Source # successors :: BiDigraph -> Vertex -> [Vertex] Source # outEdges :: BiDigraph -> Vertex -> [Edge] Source # maxVertexId :: BiDigraph -> Int Source # isEmpty :: BiDigraph -> Bool Source # edgesBetween :: BiDigraph -> Vertex -> Vertex -> [Edge] Source # | |
type MutableGraph BiDigraph Source # | |
Defined in Data.Graph.Haggle.BiDigraph |
data SimpleBiDigraph Source #
Instances
Adapters
data EdgeLabeledGraph g el Source #
Instances
data VertexLabeledGraph g nl Source #
Instances
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
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
Basic types
An abstract representation of a vertex.
Note that the representation is currently exposed. Do not rely on this, as it is subject to change.
An edge between two vertices.
edgeSource :: Edge -> Vertex Source #
Mutable graph operations
checkEdgeExists :: (MGraph g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m Bool Source #
addEdge :: (MAddEdge g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m (Maybe Edge) Source #
getEdgeLabel :: (MLabeledEdge g, PrimMonad m, MonadRef m) => g m -> Edge -> m (Maybe (MEdgeLabel g)) Source #
unsafeGetEdgeLabel :: (MLabeledEdge g, PrimMonad m, MonadRef m) => g m -> Edge -> m (MEdgeLabel g) Source #
addLabeledEdge :: (MLabeledEdge g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> MEdgeLabel g -> m (Maybe Edge) Source #
getVertexLabel :: (MLabeledVertex g, PrimMonad m, MonadRef m) => g m -> Vertex -> m (Maybe (MVertexLabel g)) Source #
addLabeledVertex :: (MLabeledVertex g, PrimMonad m, MonadRef m) => g m -> MVertexLabel g -> m Vertex Source #
getLabeledVertices :: (MLabeledVertex g, PrimMonad m, MonadRef m) => g m -> m [(Vertex, MVertexLabel g)] Source #
removeVertex :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Vertex -> m () Source #
removeEdgesBetween :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m () Source #
removeEdge :: (MRemovable g, PrimMonad m, MonadRef m) => g m -> Edge -> m () Source #
getPredecessors :: (MBidirectional g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Vertex] Source #
getInEdges :: (MBidirectional g, PrimMonad m, MonadRef m) => g m -> Vertex -> m [Edge] 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
predecessors :: Bidirectional g => g -> Vertex -> [Vertex] Source #
labeledEdges :: HasEdgeLabel g => g -> [(Edge, EdgeLabel g)] Source #
labeledOutEdges :: HasEdgeLabel g => g -> Vertex -> [(Edge, EdgeLabel g)] Source #
vertexLabel :: HasVertexLabel g => g -> Vertex -> Maybe (VertexLabel g) Source #
labeledVertices :: HasVertexLabel g => g -> [(Vertex, VertexLabel g)] Source #
labeledInEdges :: BidirectionalEdgeLabel g => g -> Vertex -> [(Edge, EdgeLabel g)] Source #
Inductive graph operations
emptyGraph :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g Source #
match :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Maybe (Context g, g) Source #
context :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Maybe (Context g) Source #
insertLabeledVertex :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> VertexLabel g -> (Vertex, g) Source #
insertLabeledEdge :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Vertex -> EdgeLabel g -> Maybe (Edge, g) Source #
deleteEdge :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Edge -> g Source #
deleteEdgesBetween :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Vertex -> g Source #
replaceLabeledEdge :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> Vertex -> EdgeLabel g -> Maybe (Edge, g) Source #
deleteVertex :: (InductiveGraph g, Graph g, HasEdgeLabel g, HasVertexLabel g) => g -> Vertex -> g Source #
Classes
These classes are a critical implementation detail, but are re-exported to simplify writing type signatures for generic functions.
The interface supported by a mutable graph.
Instances
type family ImmutableGraph g Source #
The type generated by freeze
ing a mutable graph
Instances
type ImmutableGraph MDigraph Source # | |
Defined in Data.Graph.Haggle.Digraph | |
type ImmutableGraph MBiDigraph Source # | |
Defined in Data.Graph.Haggle.BiDigraph | |
type ImmutableGraph MSimpleBiDigraph Source # | |
Defined in Data.Graph.Haggle.SimpleBiDigraph | |
type ImmutableGraph (VertexLabeledMGraph g nl) Source # | |
Defined in Data.Graph.Haggle.VertexLabelAdapter | |
type ImmutableGraph (EdgeLabeledMGraph g el) Source # | |
Defined in Data.Graph.Haggle.EdgeLabelAdapter | |
type ImmutableGraph (LabeledMGraph g nl el) Source # | |
Defined in Data.Graph.Haggle.Internal.Adapter |
class MGraph g => MAddVertex g Source #
Instances
MAddVertex MDigraph Source # | |
MAddVertex MBiDigraph Source # | |
Defined in Data.Graph.Haggle.BiDigraph | |
MAddVertex MSimpleBiDigraph Source # | |
Defined in Data.Graph.Haggle.SimpleBiDigraph | |
MAddVertex g => MAddVertex (EdgeLabeledMGraph g el) Source # | |
Defined in Data.Graph.Haggle.EdgeLabelAdapter |
class MGraph g => MLabeledEdge g Source #
Instances
type family MEdgeLabel g Source #
Instances
type MEdgeLabel (EdgeLabeledMGraph g el) Source # | |
Defined in Data.Graph.Haggle.EdgeLabelAdapter | |
type MEdgeLabel (LabeledMGraph g nl el) Source # | |
Defined in Data.Graph.Haggle.Internal.Adapter |
class MGraph g => MLabeledVertex g Source #
Instances
type family MVertexLabel g Source #
Instances
type MVertexLabel (VertexLabeledMGraph g nl) Source # | |
Defined in Data.Graph.Haggle.VertexLabelAdapter | |
type MVertexLabel (LabeledMGraph g nl el) Source # | |
Defined in Data.Graph.Haggle.Internal.Adapter |
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).
class MGraph g => MBidirectional g Source #
An interface for graphs that support looking at predecessor (incoming edges) efficiently.
Instances
The basic interface of immutable graphs.
Instances
class Graph g => Thawable g Source #
Instances
type family MutableGraph g :: (* -> *) -> * Source #
Instances
type MutableGraph Digraph Source # | |
Defined in Data.Graph.Haggle.Digraph | |
type MutableGraph BiDigraph Source # | |
Defined in Data.Graph.Haggle.BiDigraph | |
type MutableGraph SimpleBiDigraph Source # | |
Defined in Data.Graph.Haggle.SimpleBiDigraph | |
type MutableGraph (VertexLabeledGraph g nl) Source # | |
Defined in Data.Graph.Haggle.VertexLabelAdapter | |
type MutableGraph (EdgeLabeledGraph g el) Source # | |
Defined in Data.Graph.Haggle.EdgeLabelAdapter | |
type MutableGraph (LabeledGraph g nl el) Source # | |
Defined in Data.Graph.Haggle.Internal.Adapter |
class Graph g => Bidirectional g Source #
The interface for immutable graphs with efficient access to incoming edges.
Instances
class Graph g => HasEdgeLabel g Source #
The interface for immutable graphs with labeled edges.
Instances
type family EdgeLabel g Source #
Instances
type EdgeLabel (PatriciaTree nl el) Source # | |
Defined in Data.Graph.Haggle.PatriciaTree | |
type EdgeLabel (EdgeLabeledGraph g el) Source # | |
Defined in Data.Graph.Haggle.EdgeLabelAdapter | |
type EdgeLabel (LabeledGraph g nl el) Source # | |
Defined in Data.Graph.Haggle.Internal.Adapter |
class Graph g => HasVertexLabel g Source #
The interface for immutable graphs with labeled vertices.
Instances
type family VertexLabel g Source #
Instances
type VertexLabel (PatriciaTree nl el) Source # | |
Defined in Data.Graph.Haggle.PatriciaTree | |
type VertexLabel (VertexLabeledGraph g nl) Source # | |
Defined in Data.Graph.Haggle.VertexLabelAdapter | |
type VertexLabel (LabeledGraph g nl el) Source # | |
Defined in Data.Graph.Haggle.Internal.Adapter |
class (HasEdgeLabel g, Bidirectional g) => BidirectionalEdgeLabel g Source #
Instances
BidirectionalEdgeLabel (PatriciaTree nl el) Source # | |
Defined in Data.Graph.Haggle.PatriciaTree labeledInEdges :: PatriciaTree nl el -> Vertex -> [(Edge, EdgeLabel (PatriciaTree nl el))] Source # | |
Bidirectional g => BidirectionalEdgeLabel (EdgeLabeledGraph g el) Source # | |
Defined in Data.Graph.Haggle.EdgeLabelAdapter labeledInEdges :: EdgeLabeledGraph g el -> Vertex -> [(Edge, EdgeLabel (EdgeLabeledGraph g el))] Source # | |
Bidirectional g => BidirectionalEdgeLabel (LabeledGraph g nl el) Source # | |
Defined in Data.Graph.Haggle.Internal.Adapter labeledInEdges :: LabeledGraph g nl el -> Vertex -> [(Edge, EdgeLabel (LabeledGraph g nl el))] Source # |
class (Graph g, HasEdgeLabel g, HasVertexLabel g) => InductiveGraph g Source #
Instances
InductiveGraph (PatriciaTree nl el) Source # | |
Defined in Data.Graph.Haggle.PatriciaTree emptyGraph :: PatriciaTree nl el Source # match :: PatriciaTree nl el -> Vertex -> Maybe (Context (PatriciaTree nl el), PatriciaTree nl el) Source # context :: PatriciaTree nl el -> Vertex -> Maybe (Context (PatriciaTree nl el)) Source # insertLabeledVertex :: PatriciaTree nl el -> VertexLabel (PatriciaTree nl el) -> (Vertex, PatriciaTree nl el) Source # insertLabeledEdge :: PatriciaTree nl el -> Vertex -> Vertex -> EdgeLabel (PatriciaTree nl el) -> Maybe (Edge, PatriciaTree nl el) Source # deleteEdge :: PatriciaTree nl el -> Edge -> PatriciaTree nl el Source # deleteEdgesBetween :: PatriciaTree nl el -> Vertex -> Vertex -> PatriciaTree nl el Source # replaceLabeledEdge :: PatriciaTree nl el -> Vertex -> Vertex -> EdgeLabel (PatriciaTree nl el) -> Maybe (Edge, PatriciaTree nl el) Source # deleteVertex :: PatriciaTree nl el -> Vertex -> PatriciaTree nl el Source # |