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

Safe HaskellNone
LanguageHaskell2010

Data.Graph.Haggle.LabelAdapter

Contents

Synopsis

Types

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

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

Mutable Graph API

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 Graph API

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

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

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.