haggle-0.3: A graph library offering mutable, immutable, and inductive graphs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Graph.Haggle.VertexLabelAdapter

Description

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

Documentation

data VertexLabeledMGraph g nl m Source #

Instances

Instances details
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 #

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

Defined in Data.Graph.Haggle.VertexLabelAdapter

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

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type ImmutableGraph (VertexLabeledMGraph g nl) Source #

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

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type MVertexLabel (VertexLabeledMGraph g nl) Source #

type ImmutableGraph (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

type MVertexLabel (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

data VertexLabeledGraph g nl Source #

Instances

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

Defined in Data.Graph.Haggle.VertexLabelAdapter

Methods

rnf :: VertexLabeledGraph g nl -> () #

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

Defined in Data.Graph.Haggle.VertexLabelAdapter

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

Defined in Data.Graph.Haggle.VertexLabelAdapter

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

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type VertexLabel (VertexLabeledGraph g nl) 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 #

type MutableGraph (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

Mutable Graph API

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

Immutable Graph API

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,m) = 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.