subwordgraph-1.0.2: Subword graph implementation

Safe HaskellSafe
LanguageHaskell2010

Data.SubwordGraph

Contents

Description

An implementation of a classic Subword Graph (also known as Directed Acyclic Word Graph). A data structure for solving string related problems on a single word. The implementation is based on a lecture in Polish (with pseudocode): http://smurf.mimuw.edu.pl/node/581

Synopsis

Types

type Vertex = Int Source

Indicates unique id of a node.

type Edge = (Vertex, EdgeType) Source

Destination node, edge type.

type LabeledEdge a = (a, Edge) Source

Edge with its label.

type RootedEdge a = (Vertex, a, Edge) Source

Edge with its startpoint.

data EdgeType Source

Constructors

Solid 
Soft 

data Node a Source

Node structure contains the node's id, suf binding (Nothing iff root) and the map of all outgoing edges.

Instances

Eq a => Eq (Node a) Source 
Show a => Show (Node a) Source 

data SGraph a Source

Graph structure contains ids of its root and sink as well as the map of all nodes.

Instances

Eq a => Eq (SGraph a) Source 
Show a => Show (SGraph a) Source 

Construction

construct :: Ord a => [a] -> SGraph a Source

Constructs a subword graph for a given word. The performance of this function is linear in the length of a word.

constructReversed :: Ord a => [a] -> SGraph a Source

Constructs a subword graph for a reversed word. The performance of this function is linear in the length of a word.

Querying

elem :: Ord a => [a] -> SGraph a -> Bool Source

Indicates whether the subword graph contains the given word. Performance is linear in the length of the word.

subwords :: SGraph a -> [[a]] Source

Returns the list of all subwords present in a given subword graph.

subwordsNum :: SGraph a -> Int Source

Returns the number of all subwords present in the given subword graph. Performance is linear in the size of the graph.

findNode :: Ord a => [a] -> SGraph a -> Maybe (Node a) Source

Finds the given word in the subword graph. On failure, returns Nothing. On success, returns the node in the subword graph at which the word ends. Performance is linear in the length of the word.

toWord :: Ord a => SGraph a -> [a] Source

Returns a word corresponding the given subword graph. Performance is linear in the length of the word.

Traversal

foldl :: (b -> b -> RootedEdge a -> b) -> b -> SGraph a -> b Source

Folds the edges in a graph, using topological order traversal. Transformer function takes current node's state, current state along the edge, an edge and it produces a new state along the edge. Init state at node is equal to the accumulator.

foldlToNode :: (b -> b -> RootedEdge a -> b) -> b -> SGraph a -> Node a -> (b, IntMap b) Source

Folds the edges in a graph up to a given node. Returns computed value, as well as a mapping: vertex -> computed value.

foldr :: (LabeledEdge a -> b -> b -> b) -> b -> SGraph a -> b Source

Folds the edges in a graph, using post-order traversal. Transformer function takes an edge, current node's state and state along the edge. Init state at node is equal to the accumulator.

foldrFromNode :: (LabeledEdge a -> b -> b -> b) -> b -> SGraph a -> Node a -> (b, IntMap b) Source

Folds the edges in a graph starting at a given node. Returns computed value, as well as a mapping: vertex -> computed value.

topsort :: SGraph a -> [Node a] Source

For a given graph returns the list of nodes in a topological order. Performance is linear in the size of the graph.

Modification

insert :: Ord a => a -> SGraph a -> SGraph a Source

Adds an element to a given graph creating a new graph for a word with this element appended.

Others

rootId :: SGraph a -> Vertex Source

Returns id of the root.

sinkId :: SGraph a -> Vertex Source

Returns id of the sink.

nodeId :: Node a -> Vertex Source

Returns id of the node.

sufId :: Node a -> Maybe Vertex Source

Returns node's suf binding.

edges :: Node a -> Map a Edge Source

Returns node's outgoing edges.

nodesNum :: SGraph a -> Int Source

Returns number of nodes for a given graph.

edgesNum :: SGraph a -> Int Source

Returns number of edges for a given graph.

lookupNode :: Int -> SGraph a -> Maybe (Node a) Source

Returns node with a given index. Nothing iff such does not exist.

findEdge :: Ord a => Node a -> a -> Maybe Edge Source

Looks up an edge from a given node with a given label.

getRootNode :: SGraph a -> Node a Source

For a given graph returns its root node.

getSufNode :: Node a -> SGraph a -> Maybe (Node a) Source

For a given node in a given graph returns its suf link node.

getSinkNode :: SGraph a -> Node a Source

For a given graph returns its sink node.