Safe Haskell | None |
---|---|
Language | Haskell2010 |
An adapter to create graphs with labeled vertices and unlabeled edges.
See LabeledGraph
for an overview. The only significant difference
is that this graph only supports adding unlabeled edges, and thus you
must use addEdge
instead of addLabeledEdge
.
Synopsis
- data VertexLabeledMGraph g nl m
- data VertexLabeledGraph g nl
- 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)
- mapVertexLabel :: VertexLabeledGraph g nl -> (nl -> nl') -> 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)
Documentation
data VertexLabeledMGraph g nl m Source #
Instances
data VertexLabeledGraph g nl Source #
Instances
Mutable Graph API
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 #
Immutable Graph API
mapVertexLabel :: VertexLabeledGraph g nl -> (nl -> nl') -> VertexLabeledGraph g nl' Source #
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.