Safe Haskell | None |
---|---|
Language | Haskell2010 |
- module NLP.GenI.Polarity.Types
- type PolAut = NFA PolState PolTrans
- data PolState = PolSt Int [Literal GeniVal] [(Int, Int)]
- type AutDebug = (PolarityKey, PolAut, PolAut)
- data PolResult = PolResult {}
- buildAutomaton :: Set PolarityAttr -> FeatStruct GeniVal -> PolMap -> SemInput -> [TagElem] -> PolResult
- type PolPathSet = IntSet
- detectPolPaths :: [[TagElem]] -> [(TagElem, PolPathSet)]
- hasSharedPolPaths :: PolPathSet -> PolPathSet -> Bool
- polPathsToList :: PolPathSet -> [Int]
- singletonPolPath :: Int -> PolPathSet
- emptyPolPaths :: PolPathSet
- polPathsNull :: PolPathSet -> Bool
- intersectPolPaths :: PolPathSet -> PolPathSet -> PolPathSet
- unionPolPaths :: PolPathSet -> PolPathSet -> PolPathSet
- makePolAut :: [TagElem] -> Sem -> PolMap -> [PolarityKey] -> PolResult
- fixPronouns :: (Sem, [TagElem]) -> (Sem, [TagElem])
- detectSansIdx :: [TagElem] -> [TagElem]
- suggestPolFeatures :: [TagElem] -> [Text]
- detectPols :: Set PolarityAttr -> TagElem -> TagElem
- declareIdxConstraints :: Flist GeniVal -> PolMap
- detectIdxConstraints :: Flist GeniVal -> Flist GeniVal -> PolMap
- prettyPolPaths :: PolPathSet -> Text
- automatonPaths :: Ord st => NFA st ab -> [[ab]]
- finalSt :: NFA st ab -> [st]
- data NFA st ab
Documentation
module NLP.GenI.Polarity.Types
Entry point
intermediate auts, seed aut, final aut, potentially modified sem
:: Set PolarityAttr | polarities to detect (eg. "cat") |
-> FeatStruct GeniVal | root features to compensate for |
-> PolMap | explicit extra polarities |
-> SemInput | input semantics |
-> [TagElem] | lexical selection |
-> PolResult |
Constructs a polarity automaton. For debugging purposes, it returns all the intermediate automata produced by the construction algorithm.
Polarity paths
type PolPathSet = IntSet Source #
detectPolPaths :: [[TagElem]] -> [(TagElem, PolPathSet)] 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.
hasSharedPolPaths :: PolPathSet -> PolPathSet -> Bool Source #
polPathsToList :: PolPathSet -> [Int] Source #
singletonPolPath :: Int -> PolPathSet Source #
A (trivially) packed representation of the singleton set containing a single polarity path
polPathsNull :: PolPathSet -> Bool Source #
intersectPolPaths :: PolPathSet -> PolPathSet -> PolPathSet Source #
unionPolPaths :: PolPathSet -> PolPathSet -> PolPathSet Source #
Inner stuff (exported for debugging?)
makePolAut :: [TagElem] -> Sem -> PolMap -> [PolarityKey] -> PolResult Source #
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 #
suggestPolFeatures :: [TagElem] -> [Text] Source #
detectPols :: Set PolarityAttr -> TagElem -> TagElem Source #
prettyPolPaths :: PolPathSet -> Text Source #
Render the list of polarity automaton paths as a string
automatonPaths :: Ord st => 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.
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