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

Safe HaskellNone
LanguageHaskell2010

NLP.GenI.Tag

Description

This module provides basic datatypes specific to Tree Adjoining Grammar (TAG) elementary trees and some low-level operations.

Synopsis

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 #

Instances

Eq TagElem Source # 

Methods

(==) :: TagElem -> TagElem -> Bool #

(/=) :: TagElem -> TagElem -> Bool #

Data TagElem Source # 

Methods

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

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

toConstr :: TagElem -> Constr #

dataTypeOf :: TagElem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TagElem Source # 
NFData TagElem Source # 

Methods

rnf :: TagElem -> () #

GeniShow TagElem Source # 
DescendGeniVal TagElem Source # 
Idable TagElem Source # 

Methods

idOf :: TagElem -> Integer Source #

Collectable TagElem Source # 
TagItem TagElem Source # 
GeniShow [TagElem] Source # 

class TagItem t where Source #

TagItem is a generalisation of TagElem.

Minimal complete definition

tgIdName, tgIdNum, tgSemantics, tgTree

data TagSite Source #

Constructors

TagSite 

Instances

Eq TagSite Source # 

Methods

(==) :: TagSite -> TagSite -> Bool #

(/=) :: TagSite -> TagSite -> Bool #

Data TagSite Source # 

Methods

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

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

toConstr :: TagSite -> Constr #

dataTypeOf :: TagSite -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TagSite Source # 
DescendGeniVal TagSite Source # 
Pretty [TagSite] Source # 

addToTags :: Tags -> String -> TagElem -> Tags Source #

addTags tags key elem adds elem to the the list of elements associated to the key

tagLeaves :: TagElem -> [(NodeName, UninflectedDisjunction)] Source #

Normally, extracting the sentences from a TAG tree would just consist of reading its leaves. But if you want the generator to return inflected forms instead of just lemmas, you also need to return the relevant features for each leaf. In TAG, or at least our use of it, the features come from the *pre-terminal* nodes, that is, not the leaves themselves but their parents. Another bit of trickiness: because of atomic disjunction, leaves might have more than one value, so we can't just return a String lemma but a list of String, one for each possibility.

getLexeme :: GNode GeniVal -> [Text] Source #

Try in order: lexeme, lexeme attributes, node name

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.

plugTree :: Tree NodeName -> NodeName -> Tree NodeName -> Tree NodeName Source #

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!

spliceTree Source #

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.

mapBySem :: TagItem t => [t] -> Map (Literal GeniVal) [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.

collect :: Collectable a => a -> Map CollectedVar Int -> Map CollectedVar Int Source #

collect x m increments our count for any variables in x (adds not-yet-seen variables as needed)

detectSites :: Tree (GNode GeniVal) -> ([NodeName], [NodeName], [NodeName]) Source #

Given a tree(GNode) returns a list of substitution or adjunction nodes, as well as remaining nodes with a null adjunction constraint.