GenI-0.17.3: A natural language generator (specifically, an FB-LTAG surface realiser)

NLP.GenI.Geni

Synopsis

Documentation

data ProgState Source

Constructors

ST 

Fields

pa :: Params

the current configuration being processed

gr :: Macros
 
le :: Lexicon
 
morphinf :: MorphFn
 
morphlex :: Maybe [(String, String, Flist)]
 
ts :: SemInput
 
tcase :: String

names of test case to run

tsuite :: [TestCase]

name, original string (for gui), sem

traces :: [String]

simplified traces (optional)

emptyProgState :: Params -> ProgStateSource

The program state when you start GenI for the very first time

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.

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.

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 = ProgState -> IO ([TagElem], [ILexEntry])Source

Only used for instances of GenI where the grammar is compiled directly into GenI.

loadTestSuite :: ProgStateRef -> IO ()Source

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 ()Source

Updates program state the same way as loadTestSuite

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.