libGenI-0.16.1: A natural language generator (specifically, an FB-LTAG surface realiser)ContentsIndex
NLP.GenI.Geni
Synopsis
data ProgState = ST {
pa :: Params
gr :: Macros
le :: Lexicon
morphinf :: MorphFn
morphlex :: Maybe [(String, String, Flist)]
ts :: SemInput
tcase :: String
tsuite :: [TestCase]
traces :: [String]
}
type ProgStateRef = IORef ProgState
emptyProgState :: Params -> ProgState
showRealisations :: [String] -> String
groupAndCount :: (Eq a, Ord a) => [a] -> [(a, Int)]
initGeni :: ProgStateRef -> IO (Input)
runGeni :: ProgStateRef -> Builder st it Params -> IO ([GeniResult], Statistics, st)
runGeniWithSelector :: ProgStateRef -> Selector -> Builder st it Params -> IO ([GeniResult], Statistics, st)
getTraces :: ProgState -> String -> [String]
type GeniResult = (String, Derivation)
type Selector = ProgState -> IO ([TagElem], [ILexEntry])
loadEverything :: ProgStateRef -> IO ()
loadLexicon :: ProgStateRef -> IO ()
loadGeniMacros :: ProgStateRef -> IO ()
loadTestSuite :: ProgStateRef -> IO ()
loadTargetSemStr :: ProgStateRef -> String -> IO ()
combine :: Macros -> Lexicon -> Tags
chooseLexCand :: Lexicon -> Sem -> [ILexEntry]
Documentation
data ProgState
Constructors
ST
pa :: Params
gr :: Macros
le :: Lexicon
morphinf :: MorphFn
morphlex :: Maybe [(String, String, Flist)]
ts :: SemInput
tcase :: String
tsuite :: [TestCase]
traces :: [String]
type ProgStateRef = IORef ProgState
emptyProgState :: Params -> ProgState
The program state when you start GenI for the very first time
showRealisations :: [String] -> String
Show the sentences produced by the generator, in a relatively compact form
groupAndCount :: (Eq a, Ord a) => [a] -> [(a, Int)]
initGeni :: ProgStateRef -> IO (Input)
runGeni :: ProgStateRef -> Builder st it Params -> IO ([GeniResult], Statistics, st)
runGeniWithSelector :: ProgStateRef -> Selector -> Builder st it Params -> IO ([GeniResult], Statistics, st)
getTraces :: ProgState -> String -> [String]
type GeniResult = (String, Derivation)
type Selector = ProgState -> IO ([TagElem], [ILexEntry])
Only used for instances of GenI where the grammar is compiled directly into GenI.
loadEverything :: ProgStateRef -> IO ()
loadLexicon :: ProgStateRef -> IO ()
loadGeniMacros :: ProgStateRef -> IO ()
loadTestSuite :: ProgStateRef -> IO ()

The macros are stored as a hashing function in the monad.

The results are stored as a lookup function in the monad.

Stores the results in the tcase and tsuite fields

loadTargetSemStr :: ProgStateRef -> String -> IO ()
Updates program state the same way as loadTestSuite
combine :: Macros -> Lexicon -> Tags
chooseLexCand :: Lexicon -> Sem -> [ILexEntry]
Select and returns the set of entries from the lexicon whose semantics subsumes the input semantics.
Produced by Haddock version 2.1.0