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

Safe HaskellNone
LanguageHaskell2010

NLP.GenI.GeniVal.Internal

Contents

Description

Gory details for GeniVal

Synopsis

Documentation

data GeniVal Source #

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

Constructors

GeniVal 

Fields

  • gLabel :: Maybe Text

    Optional label (?X would have Just X)

  • gConstraints :: Maybe (FullList Text)

    Optional values/constraints Must have at least one if at all

    Though it may seem a bit redudant, this is not quite the same as having '[Text]' because Nothing means no constraints; whereas Just [] (impossible here) would mean bottom.

Instances

Eq GeniVal Source # 

Methods

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

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

Data GeniVal Source # 

Methods

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

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

toConstr :: GeniVal -> Constr #

dataTypeOf :: GeniVal -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeniVal Source # 
Binary GeniVal Source # 

Methods

put :: GeniVal -> Put #

get :: Get GeniVal #

putList :: [GeniVal] -> Put #

NFData GeniVal Source # 

Methods

rnf :: GeniVal -> () #

Pretty GeniVal Source # 
Pretty SemInput Source # 
Pretty Sem Source # 
GeniShow GeniVal Source # 
GeniShow SemInput Source # 
GeniShow LitConstr Source # 
GeniShow Sem Source # 
DescendGeniVal GeniVal Source # 
Collectable GeniVal Source # 
HasConstants GeniVal Source # 
Pretty (AvPair GeniVal) Source # 
Pretty (Flist GeniVal) Source # 
Pretty (Literal GeniVal) Source # 
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 (Literal GeniVal) Source # 
HasConstants (Literal GeniVal) Source # 

mkGConst Source #

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.

mkGConstNone :: Text -> GeniVal Source #

Create a singleton constant (no disjunction here)

mkGVar Source #

Arguments

:: Text

label

-> Maybe (FullList Text)

constraints

-> GeniVal 

Create a variable

mkGVarNone :: Text -> GeniVal Source #

Create a variable with no constraints

mkGAnon :: GeniVal Source #

Create an anonymous value

singletonVal :: GeniVal -> Maybe Text Source #

If v has exactly one value/constraint, returns it

isAnon :: GeniVal -> Bool Source #

An anonymous GeniVal (_ or ?_) has no labels/constraints

type Subst = Map Text GeniVal Source #

A variable substitution map. GenI unification works by rewriting variables

prettySubst :: Subst -> Text Source #

For debugging

unify :: MonadUnify 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.

allSubsume :: MonadUnify 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

unifyHelper :: MonadError String m => (GeniVal -> GeniVal -> UnificationResult) -> [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst) Source #

unifyHelper unf gs1 gs2 zips two lists with some unification function.

It's meant to serve as a helper to unify and allSubsume

appendSubst :: Subst -> Subst -> Subst Source #

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!

prependToSubst :: (Text, GeniVal) -> Subst -> Subst Source #

Add to variable replacement to a Subst that logical comes before the other stuff in it. So for example, if we have Y -> foo and we want to insert X -> Y, we notice that, in fact, Y has already been replaced by foo, so we add X -> foo instead

Note that it is undefined if you try to append something like Y -> foo to Y -> bar, because that would mean that unification is broken

data UnificationResult Source #

Unification can either…

Constructors

SuccessSans GeniVal

succeed for free (no substitutions),

SuccessRep Text GeniVal

succeed with a one-way substitution,

SuccessRep2 Text Text GeniVal

succeed w both vars needing substitution (constraint intersection),

Failure

or fail

unifyOne :: GeniVal -> GeniVal -> UnificationResult Source #

See source code for details

Note that we assume that it's acceptable to generate new variable names by appending an x to them; this assumption is only safe if the variables have gone through the function finaliseVarsById or have been pre-processed and rewritten with some kind of common suffix to avoid an accidental match

intersectConstraints :: Eq a => Maybe (FullList a) -> Maybe (FullList a) -> Maybe (Maybe (FullList a)) Source #

intersectConstraints (Just cs1) (Just cs2) returns the intersection of cs1 and cs2 if non-empty (or Nothing if there's nothing in common)

If any of the arguments is unconstrained (Nothing), we simply return the other.

subsumeOne :: GeniVal -> GeniVal -> UnificationResult Source #

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

Variable substitution

replace :: DescendGeniVal a => Subst -> a -> a Source #

Apply variable substitutions

replaceOne :: DescendGeniVal a => (Text, GeniVal) -> a -> a Source #

Apply a single variable substitution

replaceList :: DescendGeniVal a => [(Text, GeniVal)] -> a -> a Source #

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)

replaceMapG :: Subst -> GeniVal -> GeniVal Source #

Core implementation for replace For use by the Uniplate-esq descendGeniVal

replaceOneG :: (Text, GeniVal) -> GeniVal -> GeniVal Source #

Core implementation for replaceOne For use by the Uniplate-esq descendGeniVal

Variable collection and renaming

type CollectedVar = (Text, Maybe (FullList Text)) Source #

A variable label and its constraints

class Collectable a where Source #

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.

Minimal complete definition

collect

Methods

collect :: 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)

class Idable a where Source #

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.

Minimal complete definition

idOf

Methods

idOf :: a -> Integer Source #

Instances

anonymiseSingletons :: (Collectable a, DescendGeniVal a) => a -> a Source #

Anonymise any variable that occurs only once in the object

finaliseVarsById :: (Collectable a, DescendGeniVal a, Idable a) => a -> a Source #

finaliseVarsById appends a unique suffix to all variables in an object. This avoids us having to alpha convert all the time and relies on the assumption finding that a unique suffix is possible.

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

finaliseVars does the following:

  • (if suffix is non-null) appends a suffix to all variable names to ensure global uniqueness
  • intersects constraints for for all variables within the same object

Fancy disjunction

newtype 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.

Constructors

SchemaVal [GeniVal] 

crushOne :: SchemaVal -> Maybe GeniVal Source #

Convert a fancy disjunction (allowing disjunction over variables) value into a plain old atomic disjunction. The idea is to support a limited notion of fancy disjunction by requiring that there be a single point where this disjunction can be converted into a plain old variable. Note that we currently convert these to constants only.

crushList :: [SchemaVal] -> Maybe [GeniVal] Source #

Convert a list of fancy disjunctions

Genericity

class DescendGeniVal a where Source #

A structure that can be traversed with a GeniVal-replacing function (typical use case: substitution after unification)

Approach suggested by Neil Mitchell after I found that Uniplate seemed to hurt GenI performance a bit.

Minimal complete definition

descendGeniVal

Methods

descendGeniVal :: (GeniVal -> GeniVal) -> a -> a Source #

descendGeniVal f x applies f to all GeniVal in x

Instances

DescendGeniVal SchemaVal Source # 
DescendGeniVal GeniVal Source # 
DescendGeniVal LexEntry Source # 
DescendGeniVal TagElem Source # 
DescendGeniVal TagSite Source # 
DescendGeniVal UninflectedDisjunction Source # 
DescendGeniVal SimpleItem Source # 
(Functor f, DescendGeniVal a) => DescendGeniVal (f a) Source # 

Methods

descendGeniVal :: (GeniVal -> GeniVal) -> f a -> f a Source #

DescendGeniVal v => DescendGeniVal (AvPair v) Source # 
DescendGeniVal a => DescendGeniVal (Literal a) Source # 
DescendGeniVal v => DescendGeniVal (GNode v) Source # 

Methods

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

DescendGeniVal v => DescendGeniVal (Ttree v) Source # 

Methods

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