GenI-0.20: A natural language generator (specifically, an FB-LTAG surface realiser)Source codeContentsIndex
NLP.GenI.Geni
Contents
main interface
helpers
Synopsis
data ProgState = ST {
pa :: Params
gr :: Macros
le :: Lexicon
morphinf :: MorphFn
ts :: SemInput
tcase :: String
tsuite :: [TestCase]
ranking :: OtRanking
traces :: [String]
warnings :: [String]
}
type ProgStateRef = IORef ProgState
emptyProgState :: Params -> ProgState
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)
data GeniResult = GeniResult {
grLemmaSentence :: LemmaPlusSentence
grRealisations :: [String]
grDerivation :: Derivation
grLexSelection :: [GeniLexSel]
grRanking :: Int
grViolations :: [OtViolation]
grResultType :: ResultType
}
data ResultType
= CompleteResult
| PartialResult
lemmaSentenceString :: GeniResult -> String
prettyResult :: ProgState -> GeniResult -> String
showRealisations :: [String] -> String
groupAndCount :: (Eq a, Ord a) => [a] -> [(a, Int)]
getTraces :: ProgState -> String -> [String]
type Selector = ProgStateRef -> IO ([TagElem], [ILexEntry])
loadEverything :: ProgStateRef -> IO ()
loadLexicon :: ProgStateRef -> IO ()
loadGeniMacros :: ProgStateRef -> IO ()
loadTestSuite :: ProgStateRef -> IO [TestCase]
loadTargetSemStr :: ProgStateRef -> String -> IO ()
loadRanking :: ProgStateRef -> IO ()
readRanking :: Bool -> FilePath -> IO OtRanking
combine :: Macros -> Lexicon -> Tags
chooseLexCand :: Lexicon -> Sem -> [ILexEntry]
main interface
data ProgState Source
Constructors
ST
pa :: Paramsthe current configuration being processed
gr :: Macros
le :: Lexicon
morphinf :: MorphFn
ts :: SemInput
tcase :: Stringnames of test case to run
tsuite :: [TestCase]name, original string (for gui), sem
ranking :: OtRankingOT constraints (optional)
traces :: [String]simplified traces (optional)
warnings :: [String]any warnings accumulated during realisation (most recent first)
type ProgStateRef = IORef ProgStateSource
emptyProgState :: Params -> ProgStateSource
The program state when you start GenI for the very first time
initGeni :: ProgStateRef -> IO InputSource
initGeni performs lexical selection and strips the input semantics of any morpohological literals
runGeni :: ProgStateRef -> Builder st it Params -> IO ([GeniResult], Statistics, st)Source
Returns a list of sentences, a set of Statistics, and the generator state. The generator state is mostly useful for debugging via the graphical interface. Note that we assumes that you have already loaded in your grammar and parsed your input semantics.
runGeniWithSelector :: ProgStateRef -> Selector -> Builder st it Params -> IO ([GeniResult], Statistics, st)Source
data GeniResult Source
Constructors
GeniResult
grLemmaSentence :: LemmaPlusSentence
grRealisations :: [String]
grDerivation :: Derivation
grLexSelection :: [GeniLexSel]
grRanking :: Int
grViolations :: [OtViolation]
grResultType :: ResultType
show/hide Instances
data ResultType Source
Constructors
CompleteResult
PartialResult
show/hide Instances
helpers
lemmaSentenceString :: GeniResult -> StringSource
No morphology! Pretend the lemma string is a sentence
prettyResult :: ProgState -> GeniResult -> StringSource
showRealisations :: [String] -> StringSource
Show the sentences produced by the generator, in a relatively compact form
groupAndCount :: (Eq a, Ord a) => [a] -> [(a, Int)]Source
Convert a list of items into a list of tuples (a,b) where a is an item in the list and b is the number of times a in occurs in the list.
getTraces :: ProgState -> String -> [String]Source
getTraces is most likely useful for grammars produced by a metagrammar system. Given a tree name, we retrieve the `trace' information from the grammar for all trees that have this name. We assume the tree name was constructed by GenI; see the source code for details.
type Selector = ProgStateRef -> IO ([TagElem], [ILexEntry])Source
Only used for instances of GenI where the grammar is compiled directly into GenI.
loadEverything :: ProgStateRef -> IO ()Source
loadLexicon :: ProgStateRef -> IO ()Source
loadGeniMacros :: ProgStateRef -> IO ()Source
The macros are stored as a hashing function in the monad.
loadTestSuite :: ProgStateRef -> IO [TestCase]Source
Stores the results in the tcase and tsuite fields
loadTargetSemStr :: ProgStateRef -> String -> IO ()Source
Updates program state the same way as loadTestSuite
loadRanking :: ProgStateRef -> IO ()Source
readRankingSource
:: Boolverbose
-> FilePath
-> IO OtRanking
combine :: Macros -> Lexicon -> TagsSource
combine macros lex creates the Tags repository combining lexical entries and un-anchored trees from the grammar. It also unifies the parameters used to specialize un-anchored trees and propagates additional features given in the ILexEntry.
chooseLexCand :: Lexicon -> Sem -> [ILexEntry]Source
Select and returns the set of entries from the lexicon whose semantics subsumes the input semantics.
Produced by Haddock version 2.6.0