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

NLP.GenI.CkyEarley.CkyBuilder

Synopsis

Documentation

ckyBuilder :: CkyBuilderSource

earleyBuilder :: CkyBuilderSource

data CkyStatus Source

Constructors

S 

Fields

theAgenda :: Agenda
 
theChart :: Chart
 
theTrash :: Trash
 
tsemVector :: BitVector
 
theIafMap :: IafMap
 
gencounter :: Integer
 
genconfig :: Params
 
theRules :: [CKY_InferenceRule]
 
theDispatcher :: CkyItem -> CkyState (Maybe CkyItem)
 
theResults :: [CkyItem]
 
genAutCounter :: Integer
 

data CkyItem Source

Constructors

CkyItem 

Fields

ciNode :: GNode
 
ciSourceTree :: TagElem
 
ciOrigVariables :: [GeniVal]
 
ciPolpaths :: BitVector
 
ciSemantics :: BitVector
 
ciAdjPoint :: Maybe ChartId
 
ciInitialSem :: BitVector

the semantics of the item when it was first initialised

ciId :: ChartId

unique identifier for this item

ciRouting :: RoutingMap
 
ciPayload :: [CkyItem]
 
ciVariables :: [GeniVal]
 
ciSemBitMap :: SemBitMap
 
ciTreeSide :: TreeSide
 
ciDiagnostic :: [String]
 
ciDerivation :: [ChartOperation]
 
ciAccesible :: [String]
 
ciInaccessible :: [String]
 
ciSubstnodes :: [TagSite]
 

Instances

extractDerivations :: CkyStatus -> CkyItem -> [Tree (ChartId, String)]Source

Returns all the derivations trees for this item: note that this is not a TAG derivation tree but a history of inference rule applications in tree form

mAutomatonPaths :: (Ord st, Ord ab) => Maybe (NFA st ab) -> [[ab]]Source

unpackItemToAuts :: CkyStatus -> CkyItem -> SentenceAutPairMaybeSource