pedestrian-dag-0.2.0: A pedestrian implementation of directed acyclic graphs

Safe HaskellNone
LanguageHaskell98

Data.DAG

Contents

Description

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

Types

data DAG a b Source #

A directed acyclic graph (DAG) with nodes of type a and edges of type b.

Instances
Functor (DAG a) Source # 
Instance details

Defined in Data.DAG

Methods

fmap :: (a0 -> b) -> DAG a a0 -> DAG a b #

(<$) :: a0 -> DAG a b -> DAG a a0 #

Foldable (DAG a) Source # 
Instance details

Defined in Data.DAG

Methods

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 #

toList :: DAG a a0 -> [a0] #

null :: DAG a a0 -> Bool #

length :: DAG a a0 -> Int #

elem :: Eq a0 => a0 -> DAG a a0 -> Bool #

maximum :: Ord a0 => DAG a a0 -> a0 #

minimum :: Ord a0 => DAG a a0 -> a0 #

sum :: Num a0 => DAG a a0 -> a0 #

product :: Num a0 => DAG a a0 -> a0 #

Traversable (DAG a) Source # 
Instance details

Defined in Data.DAG

Methods

traverse :: Applicative f => (a0 -> f b) -> DAG a a0 -> f (DAG a b) #

sequenceA :: Applicative f => DAG a (f a0) -> f (DAG a a0) #

mapM :: Monad m => (a0 -> m b) -> DAG a a0 -> m (DAG a b) #

sequence :: Monad m => DAG a (m a0) -> m (DAG a a0) #

(Binary a, Binary b) => Binary (DAG a b) Source # 
Instance details

Defined in Data.DAG

Methods

put :: DAG a b -> Put #

get :: Get (DAG a b) #

putList :: [DAG a b] -> Put #

newtype NodeID Source #

Node ID.

Constructors

NodeID 

Fields

Instances
Eq NodeID Source # 
Instance details

Defined in Data.DAG

Methods

(==) :: NodeID -> NodeID -> Bool #

(/=) :: NodeID -> NodeID -> Bool #

Ord NodeID Source # 
Instance details

Defined in Data.DAG

Show NodeID Source # 
Instance details

Defined in Data.DAG

newtype EdgeID 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:

  • Let e be the greatest EdgeID in the DAG. Then, the set of EdgeIDs in the DAG is equal to {0 .. e}.

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).

Constructors

EdgeID 

Fields

Instances
Eq EdgeID Source # 
Instance details

Defined in Data.DAG

Methods

(==) :: EdgeID -> EdgeID -> Bool #

(/=) :: EdgeID -> EdgeID -> Bool #

Num EdgeID Source # 
Instance details

Defined in Data.DAG

Ord EdgeID Source # 
Instance details

Defined in Data.DAG

Show EdgeID Source # 
Instance details

Defined in Data.DAG

Ix EdgeID Source # 
Instance details

Defined in Data.DAG

data Edge a Source #

Edge of the DAG.

Constructors

Edge 

Fields

Instances
Functor Edge Source # 
Instance details

Defined in Data.DAG

Methods

fmap :: (a -> b) -> Edge a -> Edge b #

(<$) :: a -> Edge b -> Edge a #

Foldable Edge Source # 
Instance details

Defined in Data.DAG

Methods

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 #

toList :: Edge a -> [a] #

null :: Edge a -> Bool #

length :: Edge a -> Int #

elem :: Eq a => a -> Edge a -> Bool #

maximum :: Ord a => Edge a -> a #

minimum :: Ord a => Edge a -> a #

sum :: Num a => Edge a -> a #

product :: Num a => Edge a -> a #

Traversable Edge Source # 
Instance details

Defined in Data.DAG

Methods

traverse :: Applicative f => (a -> f b) -> Edge a -> f (Edge b) #

sequenceA :: Applicative f => Edge (f a) -> f (Edge a) #

mapM :: Monad m => (a -> m b) -> Edge a -> m (Edge b) #

sequence :: Monad m => Edge (m a) -> m (Edge a) #

Eq a => Eq (Edge a) Source # 
Instance details

Defined in Data.DAG

Methods

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

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

Ord a => Ord (Edge a) Source # 
Instance details

Defined in Data.DAG

Methods

compare :: Edge a -> Edge a -> Ordering #

(<) :: Edge a -> Edge a -> Bool #

(<=) :: Edge a -> Edge a -> Bool #

(>) :: Edge a -> Edge a -> Bool #

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

max :: Edge a -> Edge a -> Edge a #

min :: Edge a -> Edge a -> Edge a #

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

Defined in Data.DAG

Methods

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

show :: Edge a -> String #

showList :: [Edge a] -> ShowS #

Primitive Operations

begsWith :: EdgeID -> DAG a b -> NodeID Source #

Return the tail node of the given edge.

endsWith :: EdgeID -> DAG a b -> NodeID Source #

Return the head node of the given edge.

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.

nodeLabel :: NodeID -> DAG a b -> a Source #

The label assigned to the given node.

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.

edgeLabel :: EdgeID -> DAG a b -> b Source #

The label assigned to the given node.

Intermediate Operations

prevEdges :: EdgeID -> DAG a b -> [EdgeID] Source #

The list of the preceding edges of the given edge.

isInitialEdge :: EdgeID -> DAG a b -> Bool Source #

Is the given edge initial?

nextEdges :: EdgeID -> DAG a b -> [EdgeID] Source #

The list of the succeding edges of the given edge.

isFinalEdge :: EdgeID -> DAG a b -> Bool Source #

Is the given edge initial?

minEdge :: DAG a b -> EdgeID Source #

The greatest EdgeID in the DAG.

maxEdge :: DAG a b -> EdgeID Source #

The greatest EdgeID in the DAG.

mapN :: (a -> b) -> DAG a c -> DAG b c Source #

Map function over node labels.

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

dagNodes :: DAG a b -> [NodeID] Source #

The list of DAG nodes in ascending order.

dagEdges :: DAG a b -> [EdgeID] Source #

The list of DAG edges in ascending order.

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.

Check

isOK :: DAG a b -> Bool Source #

Check if the DAG is well-structured (see also isDAG).

isDAG :: DAG a b -> Bool Source #

Check if the DAG is actually acyclic.

Topological sorting

topoSort :: DAG a b -> Maybe [NodeID] Source #

Retrieve the list of nodes sorted topologically. Returns Nothing if the graph has cycles.