fgl-5.7.0.3: Martin Erwig's Functional Graph Library

Safe HaskellSafe
LanguageHaskell98

Data.Graph.Inductive.NodeMap

Contents

Description

Utility methods to automatically generate and keep track of a mapping between node labels and Nodes.

Synopsis

Functional Construction

data NodeMap a Source #

Instances
Eq a => Eq (NodeMap a) Source # 
Instance details

Defined in Data.Graph.Inductive.NodeMap

Methods

(==) :: NodeMap a -> NodeMap a -> Bool #

(/=) :: NodeMap a -> NodeMap a -> Bool #

(Ord a, Read a) => Read (NodeMap a) Source # 
Instance details

Defined in Data.Graph.Inductive.NodeMap

Show a => Show (NodeMap a) Source # 
Instance details

Defined in Data.Graph.Inductive.NodeMap

Methods

showsPrec :: Int -> NodeMap a -> ShowS #

show :: NodeMap a -> String #

showList :: [NodeMap a] -> ShowS #

NFData a => NFData (NodeMap a) Source # 
Instance details

Defined in Data.Graph.Inductive.NodeMap

Methods

rnf :: NodeMap a -> () #

Map Construction

new :: NodeMap a Source #

Create a new, empty mapping.

fromGraph :: (Ord a, Graph g) => g a b -> NodeMap a Source #

Generate a mapping containing the nodes in the given graph.

mkNode :: Ord a => NodeMap a -> a -> (LNode a, NodeMap a) Source #

Generate a labelled node from the given label. Will return the same node for the same label.

mkNode_ :: Ord a => NodeMap a -> a -> LNode a Source #

Generate a labelled node and throw away the modified NodeMap.

mkNodes :: Ord a => NodeMap a -> [a] -> ([LNode a], NodeMap a) Source #

Construct a list of nodes.

mkNodes_ :: Ord a => NodeMap a -> [a] -> [LNode a] Source #

Construct a list of nodes and throw away the modified NodeMap.

mkEdge :: Ord a => NodeMap a -> (a, a, b) -> Maybe (LEdge b) Source #

Generate a LEdge from the node labels.

mkEdges :: Ord a => NodeMap a -> [(a, a, b)] -> Maybe [LEdge b] Source #

Generates a list of LEdges.

Graph Construction

These functions mirror the construction and destruction functions in Graph, but use the given NodeMap to look up the appropriate Nodes. Note that the insMapNode family of functions will create new nodes as needed, but the other functions will not.

insMapNode :: (Ord a, DynGraph g) => NodeMap a -> a -> g a b -> (g a b, NodeMap a, LNode a) Source #

insMapNode_ :: (Ord a, DynGraph g) => NodeMap a -> a -> g a b -> g a b Source #

insMapEdge :: (Ord a, DynGraph g) => NodeMap a -> (a, a, b) -> g a b -> g a b Source #

delMapNode :: (Ord a, DynGraph g) => NodeMap a -> a -> g a b -> g a b Source #

delMapEdge :: (Ord a, DynGraph g) => NodeMap a -> (a, a) -> g a b -> g a b Source #

insMapNodes :: (Ord a, DynGraph g) => NodeMap a -> [a] -> g a b -> (g a b, NodeMap a, [LNode a]) Source #

insMapNodes_ :: (Ord a, DynGraph g) => NodeMap a -> [a] -> g a b -> g a b Source #

insMapEdges :: (Ord a, DynGraph g) => NodeMap a -> [(a, a, b)] -> g a b -> g a b Source #

delMapNodes :: (Ord a, DynGraph g) => NodeMap a -> [a] -> g a b -> g a b Source #

delMapEdges :: (Ord a, DynGraph g) => NodeMap a -> [(a, a)] -> g a b -> g a b Source #

mkMapGraph :: (Ord a, DynGraph g) => [a] -> [(a, a, b)] -> (g a b, NodeMap a) Source #

Monadic Construction

type NodeMapM a b g r = State (NodeMap a, g a b) r Source #

Graph construction monad; handles passing both the NodeMap and the Graph.

The following mirror the functional construction functions, but handle passing NodeMaps and Graphs behind the scenes.

Map Construction

run :: (DynGraph g, Ord a) => g a b -> NodeMapM a b g r -> (r, (NodeMap a, g a b)) Source #

Run a construction; return the value of the computation, the modified NodeMap, and the modified Graph.

run_ :: (DynGraph g, Ord a) => g a b -> NodeMapM a b g r -> g a b Source #

Run a construction and only return the Graph.

mkNodeM :: Ord a => a -> NodeMapM a b g (LNode a) Source #

Monadic node construction.

mkNodesM :: Ord a => [a] -> NodeMapM a b g [LNode a] Source #

mkEdgeM :: Ord a => (a, a, b) -> NodeMapM a b g (Maybe (LEdge b)) Source #

mkEdgesM :: Ord a => [(a, a, b)] -> NodeMapM a b g (Maybe [LEdge b]) Source #

Graph Construction

insMapNodeM :: (Ord a, DynGraph g) => a -> NodeMapM a b g (LNode a) Source #

insMapEdgeM :: (Ord a, DynGraph g) => (a, a, b) -> NodeMapM a b g () Source #

delMapNodeM :: (Ord a, DynGraph g) => a -> NodeMapM a b g () Source #

delMapEdgeM :: (Ord a, DynGraph g) => (a, a) -> NodeMapM a b g () Source #

insMapNodesM :: (Ord a, DynGraph g) => [a] -> NodeMapM a b g [LNode a] Source #

insMapEdgesM :: (Ord a, DynGraph g) => [(a, a, b)] -> NodeMapM a b g () Source #

delMapNodesM :: (Ord a, DynGraph g) => [a] -> NodeMapM a b g () Source #

delMapEdgesM :: (Ord a, DynGraph g) => [(a, a)] -> NodeMapM a b g () Source #