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

Safe HaskellNone
LanguageHaskell2010

NLP.GenI.FeatureStructure

Contents

Description

Feature structures in GenI can be seen as a simple mapping from attributes to values (no fancy recursion).

From an implementation standpoint, we do truck around lists of AvPair quite a bit which unfortunately means we don't guarantee things like uniqueness of attributes. We may phase this out over time in favour of FeatStruct

Synopsis

Documentation

type Flist a = [AvPair a] Source #

A list of attribute-value pairs. It's not a great idea to represent feature structures with this because it allows for duplicates in the attributes. But maybe sometimes you really do mean a list.

data AvPair a Source #

An attribute-value pair, the typical use being AvPair GeniVal or if you have something even simpler AvPair Text

Constructors

AvPair 

Fields

Instances

Pretty SemInput Source # 
GeniShow SemInput Source # 
Eq a => Eq (AvPair a) Source # 

Methods

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

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

Data a => Data (AvPair a) Source # 

Methods

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

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

toConstr :: AvPair a -> Constr #

dataTypeOf :: AvPair a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (AvPair a) Source # 

Methods

compare :: AvPair a -> AvPair a -> Ordering #

(<) :: AvPair a -> AvPair a -> Bool #

(<=) :: AvPair a -> AvPair a -> Bool #

(>) :: AvPair a -> AvPair a -> Bool #

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

max :: AvPair a -> AvPair a -> AvPair a #

min :: AvPair a -> AvPair a -> AvPair a #

Binary a => Binary (AvPair a) Source # 

Methods

put :: AvPair a -> Put #

get :: Get (AvPair a) #

putList :: [AvPair a] -> Put #

NFData a => NFData (AvPair a) Source # 

Methods

rnf :: AvPair a -> () #

Pretty (AvPair GeniVal) Source # 
Pretty (Flist GeniVal) Source # 
GeniShow gv => GeniShow (AvPair gv) Source # 
GeniShow gv => GeniShow (Flist gv) Source # 
DescendGeniVal v => DescendGeniVal (AvPair v) Source # 
Collectable a => Collectable (AvPair a) Source # 

type FeatStruct a = Map Text a Source #

Experimental, alternative representation of Flist which guarantees uniqueness of keys

emptyFeatStruct :: FeatStruct a Source #

A feature structure with no pairs

mkFeatStruct :: Flist GeniVal -> FeatStruct GeniVal Source #

Convert an Flist to a proper FeatStruct Unsafely assumes the keys are unique

fromFeatStruct :: FeatStruct a -> Flist a Source #

Convert an FeatStruct to a simpler to process Flist

sortFlist :: Flist a -> Flist a Source #

Sort an Flist according with its attributes

unifyFeat :: MonadUnify m => Flist GeniVal -> Flist GeniVal -> m (Flist GeniVal, Subst) Source #

unifyFeat performs feature structure unification, under the these assumptions about the input:

  • Features are ordered
  • The Flists do not share variables (renaming has already been done.

The features are allowed to have different sets of attributes, beacuse we use alignFeat to realign them.

alignFeat :: Flist GeniVal -> Flist GeniVal -> [(Text, GeniVal, GeniVal)] Source #

alignFeat is a pre-procesing step used to ensure that feature structures have the same set of keys. If a key is missing in one, we copy it to the other with an anonymous value.

The two feature structures must be sorted for this to work

crushAvPair :: AvPair SchemaVal -> Maybe (AvPair GeniVal) Source #

Flatten a fancy disjunction attribute-value pair

See crushOne for details

crushFlist :: Flist SchemaVal -> Maybe (Flist GeniVal) Source #

Flatten a fancy-disjunction feature structure

See crushOne for details

Orphan instances