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

Safe HaskellNone
LanguageHaskell2010

NLP.GenI.Builder

Description

The heavy lifting of GenI, the whole chart/agenda mechanism, can be implemented in many ways. To make it easier to write different algorithms for GenI and compare them, we provide a single interface for what we call Builders.

This interface is then used called by the Geni module and by the graphical interface. Note that each builder has its own graphical interface and that we do a similar thing in the graphical interface code to make it possible to use these GUIs.

Synopsis

Documentation

data Builder st it Source #

Constructors

Builder 

Fields

lexicalSelection :: TagDerivation -> [Text] Source #

The names of lexically selected chart items used in a derivation

data FilterStatus a Source #

Constructors

Filtered 
NotFiltered a 

(>-->) :: Monad s => DispatchFilter s a -> DispatchFilter s a -> DispatchFilter s a Source #

Sequence two dispatch filters.

defineSemanticBits :: Sem -> SemBitMap Source #

assign a bit vector value to each literal in the semantics the resulting map can then be used to construct a bit vector representation of the semantics

type DispatchFilter s a = a -> s (FilterStatus a) Source #

Dispatching consists of assigning a chart item to the right part of the chart (agenda, trash, results list, etc). This is implemented as a series of filters which can either fail or succeed. If a filter fails, it may modify the item before passing it on to future filters.

condFilter :: (a -> Bool) -> DispatchFilter s a -> DispatchFilter s a -> DispatchFilter s a Source #

If the item meets some condition, use the first filter, otherwise use the second one.

defaultStepAll :: Builder st it -> BuilderState st () Source #

Default implementation for the stepAll function in Builder

data UninflectedDisjunction Source #

Instances

Data UninflectedDisjunction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UninflectedDisjunction -> c UninflectedDisjunction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UninflectedDisjunction #

toConstr :: UninflectedDisjunction -> Constr #

dataTypeOf :: UninflectedDisjunction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UninflectedDisjunction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UninflectedDisjunction) #

gmapT :: (forall b. Data b => b -> b) -> UninflectedDisjunction -> UninflectedDisjunction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UninflectedDisjunction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UninflectedDisjunction -> r #

gmapQ :: (forall d. Data d => d -> u) -> UninflectedDisjunction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UninflectedDisjunction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UninflectedDisjunction -> m UninflectedDisjunction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UninflectedDisjunction -> m UninflectedDisjunction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UninflectedDisjunction -> m UninflectedDisjunction #

DescendGeniVal UninflectedDisjunction Source # 
Collectable UninflectedDisjunction Source # 

data Input Source #

Input represents the set of inputs a backend could take

Constructors

Input 

Fields

Instances

NFData Input Source # 

Methods

rnf :: Input -> () #

unlessEmptySem :: Input -> [Flag] -> a -> a Source #

Equivalent to id unless the input contains an empty or uninstatiated semantics

type SentenceAut = NFA Int LemmaPlus Source #

A SentenceAut represents a set of sentences in the form of an automaton. The labels of the automaton are the words of the sentence. But note! “word“ in the sentence is in fact a tuple (lemma, inflectional feature structures). Normally, the states are defined as integers, with the only requirement being that each one, naturally enough, is unique.

run :: Builder st it -> Input -> [Flag] -> (st, Statistics) Source #

Performs surface realisation from an input semantics and a lexical selection.

Statistics tracked

  • pol_used_bundles - number of bundled paths through the polarity automaton. see automatonPathSets
  • pol_used_paths - number of paths through the final automaton
  • pol_seed_paths - number of paths through the seed automaton (i.e. with no polarities). This is normally just 1, unless you have multi-literal semantics
  • pol_total_states - combined number of states in the all the polarity automata
  • pol_total_tras - combined number of transitions in all polarity automata
  • pol_max_states - number of states in the polarity automaton with the most states
  • pol_total_tras - number of transitions in the polarity automata with the most transitions
  • sem_literals - number of literals in the input semantics
  • lex_trees - total number of lexically selected trees