GenI-0.20.2: A natural language generator (specifically, an FB-LTAG surface realiser)Source codeContentsIndex
NLP.GenI.Polarity
Contents
Entry point
Inner stuff (exported for debugging?)
Synopsis
type PolAut = NFA PolState PolTrans
data PolState = PolSt Int [Pred] [(Int, Int)]
type AutDebug = (PolarityKey, PolAut, PolAut)
type PolResult = ([AutDebug], PolAut, PolAut, Sem)
buildAutomaton :: Set PolarityAttr -> Flist -> PolMap -> SemInput -> [TagElem] -> PolResult
makePolAut :: [TagElem] -> Sem -> PolMap -> PolResult
fixPronouns :: (Sem, [TagElem]) -> (Sem, [TagElem])
detectSansIdx :: [TagElem] -> [TagElem]
detectPolFeatures :: [TagElem] -> [String]
detectPols :: Set PolarityAttr -> [TagElem] -> [TagElem]
detectPolPaths :: [[TagElem]] -> [(TagElem, BitVector)]
declareIdxConstraints :: Flist -> PolMap
detectIdxConstraints :: Flist -> Flist -> PolMap
showLite :: ShowLite a => a -> String
showLitePm :: PolMap -> String
showPolPaths :: BitVector -> String
showPolPaths' :: BitVector -> Int -> [Int]
automatonPaths :: (Ord st, Ord ab) => NFA st ab -> [[ab]]
finalSt :: NFA st ab -> [st]
data NFA st ab
Entry point
type PolAut = NFA PolState PolTransSource
data PolState Source
Constructors
PolSt Int [Pred] [(Int, Int)]position in the input semantics, extra semantics, polarity interval
show/hide Instances
type AutDebug = (PolarityKey, PolAut, PolAut)Source
type PolResult = ([AutDebug], PolAut, PolAut, Sem)Source
intermediate auts, seed aut, final aut, potentially modified sem
buildAutomatonSource
:: Set PolarityAttrpolarities to detect
-> Flistroot features to compensate for
-> PolMapexplicit extra polarities
-> SemInputinput semantics
-> [TagElem]lexical selection
-> PolResult
Constructs a polarity automaton. For debugging purposes, it returns all the intermediate automata produced by the construction algorithm.
Inner stuff (exported for debugging?)
makePolAut :: [TagElem] -> Sem -> PolMap -> PolResultSource
fixPronouns :: (Sem, [TagElem]) -> (Sem, [TagElem])Source
Returns a modified input semantics and lexical selection in which pronouns are properly accounted for.
detectSansIdx :: [TagElem] -> [TagElem]Source
detectPolFeatures :: [TagElem] -> [String]Source
detectPols :: Set PolarityAttr -> [TagElem] -> [TagElem]Source
detectPolPaths :: [[TagElem]] -> [(TagElem, BitVector)]Source
Given a list of paths (i.e. a list of list of trees) return a list of trees such that each tree is annotated with the paths it belongs to.
declareIdxConstraints :: Flist -> PolMapSource
detectIdxConstraints :: Flist -> Flist -> PolMapSource
showLite :: ShowLite a => a -> StringSource
showLitePm :: PolMap -> StringSource
Display a PolMap in human-friendly text. The advantage is that it displays fewer quotation marks.
showPolPaths :: BitVector -> StringSource
Render the list of polarity automaton paths as a string
showPolPaths' :: BitVector -> Int -> [Int]Source
automatonPaths :: (Ord st, Ord ab) => NFA st ab -> [[ab]]Source

Returns all possible paths through an automaton from the start state to any dead-end.

Each path is represented as a list of labels.

We assume that the automaton does not have any loops in it.

finalSt :: NFA st ab -> [st]Source
finalSt returns all the final states of an automaton
data NFA st ab Source
Note: you can define the final state either by setting isFinalSt to Just f where f is some function or by putting them in finalStList
Produced by Haddock version 2.6.0