GenI-0.20.1: A natural language generator (specifically, an FB-LTAG surface realiser)Source codeContentsIndex
NLP.GenI.GeniVal
Synopsis
data GeniVal
= GConst [String]
| GVar String
| GAnon
isConst :: GeniVal -> Bool
isVar :: GeniVal -> Bool
isAnon :: GeniVal -> Bool
fromGConst :: GeniVal -> [String]
fromGVar :: GeniVal -> String
type Subst = Map String GeniVal
unify :: Monad m => [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst)
mergeSubst :: Subst -> Subst -> Subst
prependToSubst :: (String, GeniVal) -> Subst -> Subst
data UnificationResult
= SuccessSans GeniVal
| SuccessRep String GeniVal
| Failure
unifyOne :: GeniVal -> GeniVal -> UnificationResult
replace :: DescendGeniVal a => Subst -> a -> a
replaceOne :: DescendGeniVal a => (String, GeniVal) -> a -> a
replaceList :: DescendGeniVal a => [(String, GeniVal)] -> a -> a
replaceMapG :: Subst -> GeniVal -> GeniVal
replaceOneG :: (String, GeniVal) -> GeniVal -> GeniVal
class DescendGeniVal a where
descendGeniVal :: (GeniVal -> GeniVal) -> a -> a
prop_unify_self :: [GeniVal] -> Property
prop_unify_anon :: [GeniVal] -> Bool
prop_unify_sym :: [GeniVal] -> [GeniVal] -> Property
newtype GTestString = GTestString String
newtype GTestString2 = GTestString2 String
fromGTestString :: GTestString -> String
fromGTestString2 :: GTestString2 -> String
qc_not_empty_GConst :: GeniVal -> Bool
Documentation
data GeniVal Source
Constructors
GConst [String]atomic disjunction - constant x | y | z
GVar Stringvariable
GAnonanonymous
show/hide Instances
isConst :: GeniVal -> BoolSource
isVar :: GeniVal -> BoolSource
isAnon :: GeniVal -> BoolSource
fromGConst :: GeniVal -> [String]Source
(assumes that it's a GConst!)
fromGVar :: GeniVal -> StringSource
(assumes that it's a GVar!)
type Subst = Map String GeniValSource
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 verb!r! is the result of unification and verb!s! is a list of substitutions that this unification results in.
mergeSubst :: 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!

prependToSubst :: (String, GeniVal) -> Subst -> SubstSource

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
Constructors
SuccessSans GeniVal
SuccessRep String GeniVal
Failure
unifyOne :: GeniVal -> GeniVal -> UnificationResultSource
See source code for details
replace :: DescendGeniVal a => Subst -> a -> aSource
replaceOne :: DescendGeniVal a => (String, GeniVal) -> a -> aSource
replaceList :: DescendGeniVal a => [(String, 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)
replaceMapG :: Subst -> GeniVal -> GeniValSource
replaceOneG :: (String, GeniVal) -> GeniVal -> GeniValSource
class DescendGeniVal a whereSource
Methods
descendGeniVal :: (GeniVal -> GeniVal) -> a -> aSource
show/hide Instances
prop_unify_self :: [GeniVal] -> PropertySource
Unifying something with itself should always succeed
prop_unify_anon :: [GeniVal] -> BoolSource
Unifying something with only anonymous variables should succeed and return the same result.
prop_unify_sym :: [GeniVal] -> [GeniVal] -> PropertySource
Unification should be symmetrical. We can't guarantee these if there are cases where there are variables in the same place on both sides, so we normalise the sides so that this doesn't happen.
newtype GTestString Source
Constructors
GTestString String
show/hide Instances
newtype GTestString2 Source
Constructors
GTestString2 String
show/hide Instances
fromGTestString :: GTestString -> StringSource
fromGTestString2 :: GTestString2 -> StringSource
qc_not_empty_GConst :: GeniVal -> BoolSource
Produced by Haddock version 2.6.0