Safe Haskell | None |
---|---|
Language | Haskell2010 |
The heavy lifting of GenI, the whole chart/agenda mechanism, can be implemented in many ways. To make it easier to write different algorithms for GenI and compare them, we provide a single interface for what we call Builders.
This interface is then used called by the Geni module and by the graphical interface. Note that each builder has its own graphical interface and that we do a similar thing in the graphical interface code to make it possible to use these GUIs.
- type TagDerivation = [DerivationStep]
- data Builder st it = Builder {
- init :: Input -> [Flag] -> (st, Statistics)
- step :: BuilderState st ()
- stepAll :: BuilderState st ()
- finished :: st -> GenStatus
- unpack :: st -> [Output]
- partial :: st -> [Output]
- data GenStatus
- lexicalSelection :: TagDerivation -> [Text]
- data FilterStatus a
- = Filtered
- | NotFiltered a
- incrCounter :: String -> Int -> BuilderState st ()
- num_iterations :: String
- (>-->) :: Monad s => DispatchFilter s a -> DispatchFilter s a -> DispatchFilter s a
- num_comparisons :: String
- chart_size :: String
- type SemBitMap = Map (Literal GeniVal) BitVector
- defineSemanticBits :: Sem -> SemBitMap
- semToBitVector :: SemBitMap -> Sem -> BitVector
- bitVectorToSem :: SemBitMap -> BitVector -> Sem
- type DispatchFilter s a = a -> s (FilterStatus a)
- condFilter :: (a -> Bool) -> DispatchFilter s a -> DispatchFilter s a -> DispatchFilter s a
- defaultStepAll :: Builder st it -> BuilderState st ()
- type BuilderState s a = StateT s (State Statistics) a
- data UninflectedDisjunction = UninflectedDisjunction [Text] (Flist GeniVal)
- data Input = Input {
- inSemInput :: SemInput
- inLex :: [LexEntry]
- inCands :: [(TagElem, PolPathSet)]
- unlessEmptySem :: Input -> [Flag] -> a -> a
- initStats :: [Flag] -> Statistics
- type Output = (Integer, LemmaPlusSentence, TagDerivation)
- type SentenceAut = NFA Int LemmaPlus
- run :: Builder st it -> Input -> [Flag] -> (st, Statistics)
- queryCounter :: String -> Statistics -> Maybe Int
- defaultMetricNames :: [String]
- preInit :: Input -> [Flag] -> (Input, PolResult)
Documentation
type TagDerivation = [DerivationStep] Source #
Builder | |
|
lexicalSelection :: TagDerivation -> [Text] Source #
The names of lexically selected chart items used in a derivation
data FilterStatus a Source #
incrCounter :: String -> Int -> BuilderState st () Source #
(>-->) :: Monad s => DispatchFilter s a -> DispatchFilter s a -> DispatchFilter s a Source #
Sequence two dispatch filters.
chart_size :: String Source #
defineSemanticBits :: Sem -> SemBitMap Source #
assign a bit vector value to each literal in the semantics the resulting map can then be used to construct a bit vector representation of the semantics
type DispatchFilter s a = a -> s (FilterStatus a) Source #
Dispatching consists of assigning a chart item to the right part of the chart (agenda, trash, results list, etc). This is implemented as a series of filters which can either fail or succeed. If a filter fails, it may modify the item before passing it on to future filters.
condFilter :: (a -> Bool) -> DispatchFilter s a -> DispatchFilter s a -> DispatchFilter s a Source #
If the item meets some condition, use the first filter, otherwise use the second one.
defaultStepAll :: Builder st it -> BuilderState st () Source #
type BuilderState s a = StateT s (State Statistics) a Source #
Input
represents the set of inputs a backend could take
Input | |
|
unlessEmptySem :: Input -> [Flag] -> a -> a Source #
Equivalent to id
unless the input contains an empty or uninstatiated
semantics
initStats :: [Flag] -> Statistics Source #
type Output = (Integer, LemmaPlusSentence, TagDerivation) Source #
type SentenceAut = NFA Int LemmaPlus Source #
A SentenceAut represents a set of sentences in the form of an automaton. The labels of the automaton are the words of the sentence. But note! “word“ in the sentence is in fact a tuple (lemma, inflectional feature structures). Normally, the states are defined as integers, with the only requirement being that each one, naturally enough, is unique.
run :: Builder st it -> Input -> [Flag] -> (st, Statistics) Source #
Performs surface realisation from an input semantics and a lexical selection.
Statistics tracked
- pol_used_bundles - number of bundled paths through the polarity automaton.
see
automatonPathSets
- pol_used_paths - number of paths through the final automaton
- pol_seed_paths - number of paths through the seed automaton (i.e. with no polarities). This is normally just 1, unless you have multi-literal semantics
- pol_total_states - combined number of states in the all the polarity automata
- pol_total_tras - combined number of transitions in all polarity automata
- pol_max_states - number of states in the polarity automaton with the most states
- pol_total_tras - number of transitions in the polarity automata with the most transitions
- sem_literals - number of literals in the input semantics
- lex_trees - total number of lexically selected trees
queryCounter :: String -> Statistics -> Maybe Int Source #
defaultMetricNames :: [String] Source #