libGenI-0.16.1: A natural language generator (specifically, an FB-LTAG surface realiser)ContentsIndex
NLP.GenI.Morphology
Synopsis
type MorphFn = Pred -> Maybe Flist
readMorph :: [(String, [AvPair])] -> MorphFn
stripMorphSem :: MorphFn -> Sem -> Sem
attachMorph :: MorphFn -> Sem -> [TagElem] -> [TagElem]
attachMorphHelper :: Flist -> TagElem -> TagElem
setMorphAnchor :: GNode -> Tree GNode -> Tree GNode
sansMorph :: [(String, Flist)] -> [String]
type MorphLexicon = [(String, String, Flist)]
type UninflectedDisjunction = (String, Flist)
inflectSentencesUsingLex :: MorphLexicon -> [[UninflectedDisjunction]] -> [[String]]
inflectSentenceUsingLex :: MorphLexicon -> [UninflectedDisjunction] -> [String]
inflectWordUsingLex :: MorphLexicon -> UninflectedDisjunction -> [String]
inflectSentencesUsingCmd :: String -> [[UninflectedDisjunction]] -> IO [[String]]
singleton :: a -> [a]
Documentation
type MorphFn = Pred -> Maybe Flist
readMorph :: [(String, [AvPair])] -> MorphFn
stripMorphSem :: MorphFn -> Sem -> Sem
attachMorph :: MorphFn -> Sem -> [TagElem] -> [TagElem]
attachMorphHelper :: Flist -> TagElem -> TagElem
setMorphAnchor :: GNode -> Tree GNode -> Tree GNode
sansMorph :: [(String, Flist)] -> [String]
type MorphLexicon = [(String, String, Flist)]
type UninflectedDisjunction = (String, Flist)
inflectSentencesUsingLex :: MorphLexicon -> [[UninflectedDisjunction]] -> [[String]]
Return a list of results for each sentence
inflectSentenceUsingLex :: MorphLexicon -> [UninflectedDisjunction] -> [String]
inflectWordUsingLex :: MorphLexicon -> UninflectedDisjunction -> [String]
Return only n matches, but note any excessive ambiguities or missing matches
inflectSentencesUsingCmd :: String -> [[UninflectedDisjunction]] -> IO [[String]]
singleton :: a -> [a]
Produced by Haddock version 2.1.0