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

NLP.GenI.Btypes

Synopsis

Documentation

data GNode Source

Constructors

GN 

Fields

gnname :: NodeName
 
gup :: Flist
 
gdown :: Flist
 
ganchor :: Bool
 
glexeme :: [String]
 
gtype :: GType
 
gaconstr :: Bool
 
gorigin :: String

for TAG, this would be the elementary tree that this node originally came from

data Ttree a Source

Constructors

TT 

Instances

data TestCase Source

Constructors

TestCase 

Fields

tcName :: String
 
tcSemString :: String

for gui

tcSem :: SemInput
 
tcExpected :: [String]

expected results (for testing)

tcOutputs :: [(String, Map (String, String) [String])]

results we actually got, and their traces (for testing)

type Lexicon = Map String [ILexEntry]Source

A lexicon maps semantic predicates to lexical entries.

type Sem = [Pred]Source

emptyGNode :: GNodeSource

A null GNode which you can use for various debugging or display purposes.

emptyMacro :: MTtreeSource

A null tree which you can use for various debugging or display purposes.

gCategory :: Flist -> Maybe GeniValSource

Return the value of the cat attribute, if available

lexemeAttributes :: [String]Source

Attributes recognised as lexemes, in order of preference

plugTree :: Tree NodeName -> NodeName -> Tree NodeName -> Tree NodeNameSource

Plug the first tree into the second tree at the specified node. Anything below the second node is silently discarded. We assume the trees are pluggable; it is treated as a bug if they are not!

spliceTreeSource

Arguments

:: NodeName

foot node of the aux tree

-> Tree NodeName

aux tree

-> NodeName

place to adjoin in target tree

-> Tree NodeName

target tree

-> Tree NodeName 

Given two trees auxt and t, splice the tree auxt into t via the TAG adjunction rule.

root :: Tree a -> aSource

rootUpd :: Tree a -> a -> Tree aSource

setLexeme :: [String] -> Tree GNode -> Tree GNodeSource

Given a lexical item l and a tree node n (actually a subtree with no children), return the same node with the lexical item as its unique child. The idea is that it converts terminal lexeme nodes into preterminal nodes where the actual terminal is the given lexical item

setAnchor :: [String] -> Tree GNode -> Tree GNodeSource

Given a lexical item s and a Tree GNode t, returns the tree t' where l has been assigned to the anchor node in t'

toKeys :: Sem -> [String]Source

Given a Semantics, return the string with the proper keys (propsymbol+arity) to access the agenda

sortSem :: Sem -> SemSource

Sort semantics first according to its predicate, and then to its handles.

sortFlist :: Flist -> FlistSource

Sort an Flist according with its attributes

unify :: Monad m => [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst)Source

mergeSubst :: Subst -> Subst -> SubstSource

Note that the first Subst is assumed to come chronologically before the second one; so merging { X -> Y } and { Y -> 3 } should give us { X -> 3; Y -> 3 };

See prependToSubst for a warning!

class Replacable a whereSource

Methods

replace :: Subst -> a -> aSource

replaceMap :: Map String GeniVal -> a -> aSource

replaceOne :: (String, GeniVal) -> a -> aSource

replaceList :: [(String, GeniVal)] -> a -> aSource

Here it is safe to say (X -> Y; Y -> Z) because this would be crushed down into a final value of (X -> Z; Y -> Z)

replaceOneAsMap :: Replacable a => (String, GeniVal) -> a -> aSource

Default implementation for replaceOne but not a good idea for the core stuff; which is why it is not a typeclass default

class Idable a whereSource

Methods

idOf :: a -> IntegerSource

Instances

fromGConst :: GeniVal -> [String]Source

(assumes that it's a GConst!)

fromGVar :: GeniVal -> StringSource

(assumes that it's a GVar!)