Safe Haskell | None |
---|
The module implements directed acyclic word graphs (DAWGs) internaly represented as minimal acyclic deterministic finite-state automata.
In comparison to Data.DAWG.Dynamic module the automaton implemented here:
- data DAWG a b c
- type ID = Int
- rootID :: DAWG a b c -> ID
- byID :: ID -> DAWG a b c -> Maybe (DAWG a b c)
- lookup :: (Enum a, Unbox b) => [a] -> DAWG a b c -> Maybe c
- edges :: Enum a => DAWG a b c -> [(a, DAWG a b c)]
- submap :: (Enum a, Unbox b) => [a] -> DAWG a b c -> DAWG a b c
- numStates :: DAWG a b c -> Int
- numEdges :: DAWG a b c -> Int
- type Weight = Int
- weigh :: DAWG a b c -> DAWG a Weight c
- size :: DAWG a Weight c -> Int
- index :: Enum a => [a] -> DAWG a Weight c -> Maybe Int
- byIndex :: Enum a => Int -> DAWG a Weight c -> Maybe [a]
- empty :: Unbox b => DAWG a b c
- fromList :: (Enum a, Ord b) => [([a], b)] -> DAWG a () b
- fromListWith :: (Enum a, Ord b) => (b -> b -> b) -> [([a], b)] -> DAWG a () b
- fromLang :: Enum a => [[a]] -> DAWG a () ()
- assocs :: (Enum a, Unbox b) => DAWG a b c -> [([a], c)]
- keys :: (Enum a, Unbox b) => DAWG a b c -> [[a]]
- elems :: Unbox b => DAWG a b c -> [c]
- freeze :: DAWG a b -> DAWG a () b
DAWG type
ID
rootID :: DAWG a b c -> IDSource
The actual DAWG root has the 0 ID. Thanks to the rootID
attribute, we can represent a submap of a DAWG.
byID :: ID -> DAWG a b c -> Maybe (DAWG a b c)Source
Retrieve sub-DAWG with a given ID (or Nothing
, if there's
no such DAWG). This function can be used, together with the
root
function, to store IDs rather than entire DAWGs in a
data structure.
Query
lookup :: (Enum a, Unbox b) => [a] -> DAWG a b c -> Maybe cSource
Find value associated with the key.
submap :: (Enum a, Unbox b) => [a] -> DAWG a b c -> DAWG a b cSource
Return the sub-DAWG containing all keys beginning with a prefix. The in-memory representation of the resultant DAWG is the same as of the original one, only the pointer to the DAWG root will be different.
Weight
Weight of a node corresponds to the number of final states reachable from the node. Weight of an edge is a sum of weights of preceding nodes outgoing from the same parent node.
weigh :: DAWG a b c -> DAWG a Weight cSource
Compute node weights and store corresponding values in transition labels.
Be aware, that the entire DAWG will be weighted, even when (because of the use of
the submap
function) only a part of the DAWG is currently selected.
index :: Enum a => [a] -> DAWG a Weight c -> Maybe IntSource
Position in a set of all dictionary entries with respect to the lexicographic order.
byIndex :: Enum a => Int -> DAWG a Weight c -> Maybe [a]Source
Find dictionary entry given its index with respect to the lexicographic order.
Construction
fromListWith :: (Enum a, Ord b) => (b -> b -> b) -> [([a], b)] -> DAWG a () bSource
Conversion
assocs :: (Enum a, Unbox b) => DAWG a b c -> [([a], c)]Source
Return all (key, value) pairs in the DAWG in ascending key order.
keys :: (Enum a, Unbox b) => DAWG a b c -> [[a]]Source
Return all keys of the DAWG in ascending order.