Safe Haskell | None |
---|
A DAWG
-based dictionary with additional information
assigned to lexical entries and word forms.
- data Rule = Rule {}
- apply :: Rule -> Text -> Text
- between :: Text -> Text -> Rule
- data Lex i a b = Lex {}
- data Key i = Key {}
- data Val a w b = Val {}
- type LexSet i a b = Map (Key i) (Val a Text b)
- mkLexSet :: Ord i => [Lex i a b] -> LexSet i a b
- unLexSet :: LexSet i a b -> [Lex i a b]
- type Node i a b = Map i (Val a Rule b)
- decode :: Ord i => Text -> Node i a b -> LexSet i a b
- type DAWG i a b = DAWG Char Weight (Node i a b)
- type DAWG'Init i a b = DAWG Char (Node i a b)
- empty :: Ord b => DAWG a b
- insert :: (Ord i, Ord a, Ord b) => (Text, i, a, Text, b) -> DAWG'Init i a b -> DAWG'Init i a b
- freeze :: DAWG a b -> DAWG a () b
- lookup :: Ord i => Text -> DAWG i a b -> LexSet i a b
- submap :: Ord i => Text -> DAWG i a b -> DAWG i a b
- type Weight = Int
- weigh :: DAWG a b c -> DAWG a Weight c
- size :: DAWG a Weight c -> Int
- index :: Text -> DAWG i a b -> Maybe Int
- byIndex :: Int -> DAWG i a b -> Maybe Text
- fromList :: (Ord i, Ord a, Ord b) => [(Text, i, a, Text, b)] -> DAWG i a b
- toList :: (Ord i, Ord a, Ord b) => DAWG i a b -> [(Text, i, a, Text, b)]
- entries :: Ord i => DAWG i a b -> [Lex i a b]
- revDAWG :: (Ord i, Ord a, Ord b) => DAWG i a b -> DAWG i a b
Rule
A rule for translating a form into another form.
Entry
A key of a dictionary entry.
A value of the entry.
Entry set
type Node i a b = Map i (Val a Rule b)Source
Actual values stored in automaton states contain
all entry information but path
.
DAWG
type DAWG i a b = DAWG Char Weight (Node i a b)Source
A dictionary parametrized over ID i
, with info a
for every
(key, i) pair and info b
for every (key, i, apply rule key) triple.
Initialization
type DAWG'Init i a b = DAWG Char (Node i a b)Source
A DAWG
initialization structure (a dynamic DAWG).
insert :: (Ord i, Ord a, Ord b) => (Text, i, a, Text, b) -> DAWG'Init i a b -> DAWG'Init i a bSource
Insert a (key, ID, entry info, form, entry/form info) into a
DAWG'Init
structure.
Query
submap :: Ord i => Text -> DAWG i a b -> DAWG i a bSource
Return the sub-dictionary containing all keys beginning with a prefix.
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 c
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 :: Text -> DAWG i a b -> Maybe IntSource
Position in a set of all dictionary entries with respect to the lexicographic order.
byIndex :: Int -> DAWG i a b -> Maybe TextSource
Find dictionary entry given its index with respect to the lexicographic order.
Conversion
fromList :: (Ord i, Ord a, Ord b) => [(Text, i, a, Text, b)] -> DAWG i a bSource
Make dictionary from a list of (key, ID, entry info, form, entry/form info) tuples.