Safe Haskell | None |
---|---|
Language | Haskell98 |
A pedestrian implementation of a directed acyclic graph. Sharing is explicitely represented by using node-level and edge-level identifiers. The module may be convenient to use if your data structure doesn't change often.
Synopsis
- data DAG a b
- newtype NodeID = NodeID {}
- newtype EdgeID = EdgeID {}
- data Edge a = Edge {}
- begsWith :: EdgeID -> DAG a b -> NodeID
- endsWith :: EdgeID -> DAG a b -> NodeID
- ingoingEdges :: NodeID -> DAG a b -> [EdgeID]
- outgoingEdges :: NodeID -> DAG a b -> [EdgeID]
- maybeNodeLabel :: NodeID -> DAG a b -> Maybe a
- nodeLabel :: NodeID -> DAG a b -> a
- maybeEdgeLabel :: EdgeID -> DAG a b -> Maybe b
- edgeLabel :: EdgeID -> DAG a b -> b
- prevEdges :: EdgeID -> DAG a b -> [EdgeID]
- isInitialEdge :: EdgeID -> DAG a b -> Bool
- nextEdges :: EdgeID -> DAG a b -> [EdgeID]
- isFinalEdge :: EdgeID -> DAG a b -> Bool
- minEdge :: DAG a b -> EdgeID
- maxEdge :: DAG a b -> EdgeID
- mapN :: (a -> b) -> DAG a c -> DAG b c
- mapE :: (EdgeID -> b -> c) -> DAG a b -> DAG a c
- zipE :: DAG a b -> DAG x c -> DAG a (b, c)
- zipE' :: DAG x a -> DAG y b -> DAG () (Maybe a, Maybe b)
- dagNodes :: DAG a b -> [NodeID]
- dagEdges :: DAG a b -> [EdgeID]
- fromList :: [a] -> DAG () a
- fromList' :: a -> [(a, b)] -> DAG a b
- fromEdgesUnsafe :: [Edge a] -> DAG () a
- splitTmp :: NodeID -> DAG a b -> Maybe (DAG a b, DAG a b)
- filterDAG :: Set EdgeID -> DAG a b -> DAG a b
- isOK :: DAG a b -> Bool
- isDAG :: DAG a b -> Bool
- topoSort :: DAG a b -> Maybe [NodeID]
Types
A directed acyclic graph (DAG) with nodes of type a
and
edges of type b
.
Instances
Functor (DAG a) Source # | |
Foldable (DAG a) Source # | |
Defined in Data.DAG fold :: Monoid m => DAG a m -> m # foldMap :: Monoid m => (a0 -> m) -> DAG a a0 -> m # foldr :: (a0 -> b -> b) -> b -> DAG a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> DAG a a0 -> b # foldl :: (b -> a0 -> b) -> b -> DAG a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> DAG a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> DAG a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> DAG a a0 -> a0 # elem :: Eq a0 => a0 -> DAG a a0 -> Bool # maximum :: Ord a0 => DAG a a0 -> a0 # minimum :: Ord a0 => DAG a a0 -> a0 # | |
Traversable (DAG a) Source # | |
(Binary a, Binary b) => Binary (DAG a b) Source # | |
ID of an edge. The following properties must be satisfied by EdgeID
:
- The ordering of edge IDs (
Ord
instance) is consistent with the topological ordering of the edges. (TODO 26022018: be more specific about what consistency means in this context) - The smallest
EdgeID
of a given DAG,minEdge
, is equal to `0` (`EdgeID 0`).
Additional important property, which guarantees that inference computations over the DAG, based on dynamic programming, are efficient:
However, this last property is not required for the correcntess of the inference computations, it only improves their memory complexity.
TODO (13112017): It seems that the following is not required:
* The smallest EdgeID
of a given DAG, minEdge
, is equal
to `0` (`EdgeID 0`).
Verify that (see also splitTmp
, whose second element does not satisfy the
above description)!
TODO (26022018): Perhaps we should also assume that node IDs are sorted
topologically? (see splitTmp
).
Edge of the DAG.
Instances
Functor Edge Source # | |
Foldable Edge Source # | |
Defined in Data.DAG fold :: Monoid m => Edge m -> m # foldMap :: Monoid m => (a -> m) -> Edge a -> m # foldr :: (a -> b -> b) -> b -> Edge a -> b # foldr' :: (a -> b -> b) -> b -> Edge a -> b # foldl :: (b -> a -> b) -> b -> Edge a -> b # foldl' :: (b -> a -> b) -> b -> Edge a -> b # foldr1 :: (a -> a -> a) -> Edge a -> a # foldl1 :: (a -> a -> a) -> Edge a -> a # elem :: Eq a => a -> Edge a -> Bool # maximum :: Ord a => Edge a -> a # | |
Traversable Edge Source # | |
Eq a => Eq (Edge a) Source # | |
Ord a => Ord (Edge a) Source # | |
Show a => Show (Edge a) Source # | |
Primitive Operations
ingoingEdges :: NodeID -> DAG a b -> [EdgeID] Source #
The list of outgoint edges from the given node, in ascending order.
outgoingEdges :: NodeID -> DAG a b -> [EdgeID] Source #
The list of outgoint edges from the given node, in ascending order.
maybeNodeLabel :: NodeID -> DAG a b -> Maybe a Source #
The label assigned to the given node. Return Nothing
if the node ID is
out of bounds.
maybeEdgeLabel :: EdgeID -> DAG a b -> Maybe b Source #
The label assigned to the given edge. Return Nothing
if the edge ID is
out of bounds.
Intermediate Operations
prevEdges :: EdgeID -> DAG a b -> [EdgeID] Source #
The list of the preceding edges of the given edge.
nextEdges :: EdgeID -> DAG a b -> [EdgeID] Source #
The list of the succeding edges of the given edge.
mapE :: (EdgeID -> b -> c) -> DAG a b -> DAG a c Source #
Similar to fmap
but the mapping function has access to IDs of the
individual edges.
zipE :: DAG a b -> DAG x c -> DAG a (b, c) Source #
Zip labels assigned to the same edges in the two input DAGs. Node labels from the first DAG are preserved. The function fails if the input DAGs contain different sets of edge IDs or node IDs.
zipE' :: DAG x a -> DAG y b -> DAG () (Maybe a, Maybe b) Source #
A version of zipE
which does not require that the sets of edges/nodes be
the same. It does not preserve the node labels, though (it could be probably
easily modified so as to account for them, though).
Advanced Operations
Conversion
fromList :: [a] -> DAG () a Source #
Convert a sequence of items to a trivial DAG. Afterwards, check if the resulting DAG is well-structured and throw error if not.
fromList' :: a -> [(a, b)] -> DAG a b Source #
Convert a sequence of items to a trivial DAG. Afterwards, check if the resulting DAG is well-structured and throw error if not.
fromEdgesUnsafe :: [Edge a] -> DAG () a Source #
Convert a sequence of labeled edges into a dag. The function assumes that edges are given in topological order.
Splitting
splitTmp :: NodeID -> DAG a b -> Maybe (DAG a b, DAG a b) Source #
Try to split the DAG on the given node, so that all the fst element of the result contains all nodes and edges from the given node is reachable, while the snd element contains all nodes/edges reachable from this node.
NOTE: some edges can be discarded this way, it seems!
TODO: A provisional function which does not necessarily work correctly. Now it assumes that node IDs are sorted topologically.
Filtering
filterDAG :: Set EdgeID -> DAG a b -> DAG a b Source #
Remove the edges (and the corresponding nodes) which are not in the given set.