GenI-0.20: A natural language generator (specifically, an FB-LTAG surface realiser)Source codeContentsIndex
NLP.GenI.Tags
Synopsis
type Tags = Map String [TagElem]
data TagElem = TE {
idname :: String
ttreename :: String
tidnum :: Integer
ttype :: Ptype
ttree :: Tree GNode
tsemantics :: Sem
tpolarities :: Map PolarityKey (Int, Int)
tinterface :: Flist
ttrace :: [String]
tsempols :: [SemPols]
}
class TagItem t where
tgIdName :: t -> String
tgIdNum :: t -> Integer
tgSemantics :: t -> Sem
data TagSite = TagSite {
tsName :: String
tsUp :: Flist
tsDown :: Flist
tsOrigin :: String
}
type TagDerivation = [DerivationStep]
data DerivationStep = DerivationStep {
dsOp :: Char
dsChild :: String
dsParent :: String
dsParentSite :: String
}
emptyTE :: TagElem
ts_synIncomplete :: String
ts_semIncomplete :: [Pred] -> String
ts_tbUnificationFailure :: String
ts_rootFeatureMismatch :: Flist -> String
addToTags :: Tags -> String -> TagElem -> Tags
tagLeaves :: TagElem -> [(String, UninflectedDisjunction)]
setTidnums :: [TagElem] -> [TagElem]
mapBySem :: TagItem t => [t] -> Map Pred [t]
subsumedBy :: Sem -> Pred -> Bool
showTagSites :: [TagSite] -> String
collect :: Collectable a => a -> Set String -> Set String
detectSites :: Tree GNode -> ([TagSite], [TagSite], [TagSite])
Documentation
type Tags = Map String [TagElem]Source
An anchored grammar. The grammar associates a set of semantic predicates to a list of trees each.
data TagElem Source
Constructors
TE
idname :: String
ttreename :: String
tidnum :: Integer
ttype :: Ptype
ttree :: Tree GNode
tsemantics :: Sem
tpolarities :: Map PolarityKey (Int, Int)
tinterface :: Flist
ttrace :: [String]
tsempols :: [SemPols]
show/hide Instances
class TagItem t whereSource
TagItem is a generalisation of TagElem.
Methods
tgIdName :: t -> StringSource
tgIdNum :: t -> IntegerSource
tgSemantics :: t -> SemSource
show/hide Instances
data TagSite Source
Constructors
TagSite
tsName :: String
tsUp :: Flist
tsDown :: Flist
tsOrigin :: String
show/hide Instances
type TagDerivation = [DerivationStep]Source
data DerivationStep Source
Constructors
DerivationStep
dsOp :: Char
dsChild :: String
dsParent :: String
dsParentSite :: String
show/hide Instances
emptyTE :: TagElemSource
ts_synIncomplete :: StringSource
ts_semIncomplete :: [Pred] -> StringSource
ts_tbUnificationFailure :: StringSource
ts_rootFeatureMismatch :: Flist -> StringSource
addToTags :: Tags -> String -> TagElem -> TagsSource
addTags tags key elem adds elem to the the list of elements associated to the key
tagLeaves :: TagElem -> [(String, UninflectedDisjunction)]Source
setTidnums :: [TagElem] -> [TagElem]Source
Assigns a unique id to each element of this list, that is, an integer between 1 and the size of the list.
mapBySem :: TagItem t => [t] -> Map Pred [t]Source
Sorts trees into a Map.Map organised by the first literal of their semantics. This is useful in at least three places: the polarity optimisation, the gui display code, and code for measuring the efficiency of GenI. Note: trees with a null semantics are filed under an empty predicate, if any.
subsumedBy :: Sem -> Pred -> BoolSource

subsumedBy cs ts determines if the candidate semantics cs is subsumed by the proposition semantics ts. Notice how the proposition semantics is only a single item where as the candidate semantics is a list.

We assume

  • most importantly that cs has already its semantics instatiated (all variables assigned)
  • cs and ts are sorted
  • the list in each element of cs and ts is itself sorted
showTagSites :: [TagSite] -> StringSource
collect :: Collectable a => a -> Set String -> Set StringSource
detectSites :: Tree GNode -> ([TagSite], [TagSite], [TagSite])Source
Given a tree(GNode) returns a list of substitution or adjunction nodes, as well as remaining nodes with a null adjunction constraint.
Produced by Haddock version 2.6.0