GenI-0.20.2: A natural language generator (specifically, an FB-LTAG surface realiser)Source codeContentsIndex
NLP.GenI.Morphology
Contents
Morphological predicates
Morphological realisation
Synopsis
type MorphFn = Pred -> Maybe Flist
data LemmaPlus = LemmaPlus {
lpLemma :: String
lpFeats :: Flist
}
type LemmaPlusSentence = [LemmaPlus]
readMorph :: [(String, [AvPair])] -> MorphFn
stripMorphSem :: MorphFn -> Sem -> Sem
attachMorph :: MorphFn -> Sem -> [TagElem] -> [TagElem]
setMorphAnchor :: GNode -> Tree GNode -> Tree GNode
inflectSentencesUsingCmd :: String -> [LemmaPlusSentence] -> IO [(LemmaPlusSentence, [String])]
sansMorph :: LemmaPlusSentence -> [String]
Documentation
type MorphFn = Pred -> Maybe FlistSource
data LemmaPlus Source
A lemma plus its morphological features
Constructors
LemmaPlus
lpLemma :: String
lpFeats :: Flist
show/hide Instances
type LemmaPlusSentence = [LemmaPlus]Source
A sentence composed of LemmaPlus instead of plain old words
Morphological predicates
readMorph :: [(String, [AvPair])] -> MorphFnSource
Converts information from a morphological information file into GenI's internal format.
stripMorphSem :: MorphFn -> Sem -> SemSource
Filters away from an input semantics any literals whose realisation is strictly morphological. The first argument tells us helps identify the morphological literals -- it associates literals with morphological stuff; if it returns Nothing, then it is non-morphological
attachMorph :: MorphFn -> Sem -> [TagElem] -> [TagElem]Source
attachMorph morphfn sem cands does the bulk of the morphological input processing. We use morphfn to determine which literals in sem contain morphological information and what information they contain. Then we attach this morphological information to the relevant trees in cand. A tree is considered relevant w.r.t to a morphological literal if its semantics contains at least one literal whose first index is the same as the first index of the morphological literal.
setMorphAnchor :: GNode -> Tree GNode -> Tree GNodeSource
Morphological realisation
inflectSentencesUsingCmd :: String -> [LemmaPlusSentence] -> IO [(LemmaPlusSentence, [String])]Source
Converts a list of uninflected sentences into inflected ones by calling
sansMorph :: LemmaPlusSentence -> [String]Source
Extracts the lemmas from a list of uninflected sentences. This is used when the morphological generator is unavailable, doesn't work, etc.
Produced by Haddock version 2.6.0