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

Safe HaskellNone

NLP.GenI.GeniVal

Contents

Synopsis

GeniVal

data GeniVal Source

constant : no label, just constraints variable : label, with or without constraints anonymous : no label, no constraints

Instances

Eq GeniVal 
Data GeniVal 
Ord GeniVal 
Typeable GeniVal 
Binary GeniVal 
NFData GeniVal 
Pretty GeniVal 
Pretty SemInput 
Pretty Sem 
GeniShow GeniVal 
GeniShow SemInput 
GeniShow Sem 
DescendGeniVal GeniVal 
Collectable GeniVal 
HasConstants GeniVal 
GeniValLike GeniVal 
Loadable Macros 
Pretty (FeatStruct GeniVal) 
Pretty (AvPair GeniVal) 
Pretty (Flist GeniVal) 
Pretty (Literal GeniVal) 
Pretty (GNode GeniVal)

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 (FeatStruct GeniVal) 
GeniShow (AvPair GeniVal) 
GeniShow (Flist GeniVal) 
GeniShow (Literal GeniVal) 
GeniShow (GNode GeniVal) 
HasConstants (Literal GeniVal) 
GeniValLike [GeniVal] 

mkGConstSource

Arguments

:: FullList Text

non-empty list

-> GeniVal 

mkGConst x :! [] creates a single constant. mkGConst x :! xs creates an atomic disjunction. It makes no difference which of the values you supply for x and xs as they will be sorted and nubed anyway.

queries and manipulation

Unification and subsumption

Finalisation

finaliseVars :: (Collectable a, DescendGeniVal a) => Text -> a -> aSource

finaliseVars does the following:

  • (if suffix is non-null) appends a suffix to all variable names to ensure global uniqueness
  • anonymises any singleton variables

Unification

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

unify performs unification on two lists of GeniVal. If unification succeeds, it returns Just (r,s) where r is the result of unification and verb!s! is a list of substitutions that this unification results in.

appendSubst :: 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!

subsumption

subsumeOne :: GeniVal -> GeniVal -> UnificationResultSource

subsumeOne x y returns the same result as unifyOne x y if x subsumes y or Failure otherwise

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

l1 allSubsume l2 returns the result of l1 unify l2 if doing a simultaneous traversal of both lists, each item in l1 subsumes the corresponding item in l2

Traversing GeniVal containers

class Collectable a whereSource

A Collectable is something which can return its variables as a map from the variable to the number of times that variable occurs in it.

Important invariant: if the variable does not occur, then it does not appear in the map (ie. all counts must be >= 1 or the item does not occur at all)

By variables, what I most had in mind was the GVar values in a GeniVal. This notion is probably not very useful outside the context of alpha-conversion task, but it seems general enough that I'll keep it around for a good bit, until either some use for it creeps up, or I find a more general notion that I can transform this into.

class Idable a whereSource

An Idable is something that can be mapped to a unique id. You might consider using this to implement Ord, but I won't. Note that the only use I have for this so far (20 dec 2005) is in alpha-conversion.

Methods

idOf :: a -> IntegerSource

Instances

replaceList :: DescendGeniVal a => [(Text, 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)