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

Safe HaskellNone
LanguageHaskell2010

NLP.GenI.TreeSchema

Contents

Description

This module provides basic datatypes specific to Tree Adjoining Grammar tree schemata.

Synopsis

Documentation

data Ttree a Source #

Constructors

TT 

Instances

Loadable Macros Source # 
Eq a => Eq (Ttree a) Source # 

Methods

(==) :: Ttree a -> Ttree a -> Bool #

(/=) :: Ttree a -> Ttree a -> Bool #

Data a => Data (Ttree a) Source # 

Methods

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

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

toConstr :: Ttree a -> Constr #

dataTypeOf :: Ttree a -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary a => Binary (Ttree a) Source # 

Methods

put :: Ttree a -> Put #

get :: Get (Ttree a) #

putList :: [Ttree a] -> Put #

GeniShow a => GeniShow [Ttree a] Source # 
GeniShow a => GeniShow (Ttree a) Source # 
DescendGeniVal v => DescendGeniVal (Ttree v) Source # 

Methods

descendGeniVal :: (GeniVal -> GeniVal) -> Ttree v -> Ttree v Source #

Collectable a => Collectable (Ttree a) Source # 

data Ptype Source #

Constructors

Initial 
Auxiliar 

Instances

Eq Ptype Source # 

Methods

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

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

Data Ptype Source # 

Methods

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

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

toConstr :: Ptype -> Constr #

dataTypeOf :: Ptype -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Ptype Source # 

Methods

showsPrec :: Int -> Ptype -> ShowS #

show :: Ptype -> String #

showList :: [Ptype] -> ShowS #

Binary Ptype Source # 

Methods

put :: Ptype -> Put #

get :: Get Ptype #

putList :: [Ptype] -> Put #

NFData Ptype Source # 

Methods

rnf :: Ptype -> () #

GeniShow Ptype Source # 

root :: Tree a -> a Source #

rootUpd :: Tree a -> a -> Tree a Source #

foot :: Tree (GNode a) -> GNode a Source #

setLexeme :: [Text] -> Tree (GNode a) -> Tree (GNode a) Source #

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 :: FullList Text -> Tree (GNode a) -> Tree (GNode a) Source #

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'

lexemeAttributes :: [Text] Source #

Attributes recognised as lexemes, in order of preference

data AdjunctionConstraint Source #

Essentially boolean representation of adjunction constraint

Constructors

MaybeAdj 
ExplicitNoAdj

hard-coded null-adjunction constraint

InferredNoAdj

inferred by GenI to be adjunction free (ie. during realisation)

Instances

Eq AdjunctionConstraint Source # 
Data AdjunctionConstraint Source # 

Methods

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

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

toConstr :: AdjunctionConstraint -> Constr #

dataTypeOf :: AdjunctionConstraint -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary AdjunctionConstraint Source # 
NFData AdjunctionConstraint Source # 

Methods

rnf :: AdjunctionConstraint -> () #

addInferredAdjConstraint :: GNode gv -> GNode gv Source #

Add an inferred adjunction constraint marker unless we already see an explicit one

data GNode gv Source #

A single node of a TAG tree.

Constructors

GN 

Fields

Instances

Loadable Macros Source # 
Eq gv => Eq (GNode gv) Source # 

Methods

(==) :: GNode gv -> GNode gv -> Bool #

(/=) :: GNode gv -> GNode gv -> Bool #

Data gv => Data (GNode gv) Source # 

Methods

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

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

toConstr :: GNode gv -> Constr #

dataTypeOf :: GNode gv -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary gv => Binary (GNode gv) Source # 

Methods

put :: GNode gv -> Put #

get :: Get (GNode gv) #

putList :: [GNode gv] -> Put #

NFData gv => NFData (GNode gv) Source #

A single node of a TAG tree.

Methods

rnf :: GNode gv -> () #

Pretty (GNode GeniVal) Source #

The default show for GNode tries to be very compact; it only shows the value for cat attribute and any flags which are marked on that node.

This is one the places where the pretty representation of a GenI object is different from its GenI-format one

GeniShow gv => GeniShow (GNode gv) Source # 
DescendGeniVal v => DescendGeniVal (GNode v) Source # 

Methods

descendGeniVal :: (GeniVal -> GeniVal) -> GNode v -> GNode v Source #

Collectable gv => Collectable (GNode gv) Source # 

data GType Source #

Constructors

Subs 
Foot 
Lex 
Other 

Instances

Eq GType Source # 

Methods

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

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

Data GType Source # 

Methods

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

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

toConstr :: GType -> Constr #

dataTypeOf :: GType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GType Source # 

Methods

showsPrec :: Int -> GType -> ShowS #

show :: GType -> String #

showList :: [GType] -> ShowS #

Binary GType Source # 

Methods

put :: GType -> Put #

get :: Get GType #

putList :: [GType] -> Put #

NFData GType Source # 

Methods

rnf :: GType -> () #

gCategory :: Flist GeniVal -> Maybe GeniVal Source #

Return the value of the "cat" attribute, if available

Fancy disjunction

data SchemaVal Source #

A schema value is a disjunction of GenI values. It allows us to express “fancy” disjunctions in tree schemata, ie. disjunctions over variables and not just atoms (?X;?Y).

Our rule is that that when a tree schema is instantiated, any fancy disjunctions must be “crushed” into a single GeniVal lest it be rejected (see crushOne)

Note that this is still not recursive; we don't have disjunction over schema values, nor can schema values refer to schema values. It just allows us to express the idea that in tree schemata, you can have either variable ?X or ?Y.

Orphan instances