| Safe Haskell | None |
|---|
NLP.GenI.GeniVal.Internal
- data GeniVal = GeniVal {}
- mkGConst :: FullList Text -> GeniVal
- mkGConstNone :: Text -> GeniVal
- mkGVar :: Text -> Maybe (FullList Text) -> GeniVal
- mkGVarNone :: Text -> GeniVal
- mkGAnon :: GeniVal
- isConst :: GeniVal -> Bool
- singletonVal :: GeniVal -> Maybe Text
- isVar :: GeniVal -> Bool
- isAnon :: GeniVal -> Bool
- type Subst = Map Text GeniVal
- prettySubst :: Subst -> Text
- unify :: Monad m => [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst)
- allSubsume :: Monad m => [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst)
- unifyHelper :: Monad m => (GeniVal -> GeniVal -> UnificationResult) -> [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst)
- appendSubst :: Subst -> Subst -> Subst
- prependToSubst :: (Text, GeniVal) -> Subst -> Subst
- data UnificationResult
- unifyOne :: GeniVal -> GeniVal -> UnificationResult
- intersectConstraints :: Eq a => Maybe (FullList a) -> Maybe (FullList a) -> Maybe (Maybe (FullList a))
- subsumeOne :: GeniVal -> GeniVal -> UnificationResult
- replace :: DescendGeniVal a => Subst -> a -> a
- replaceOne :: DescendGeniVal a => (Text, GeniVal) -> a -> a
- replaceList :: DescendGeniVal a => [(Text, GeniVal)] -> a -> a
- replaceMapG :: Subst -> GeniVal -> GeniVal
- replaceOneG :: (Text, GeniVal) -> GeniVal -> GeniVal
- type CollectedVar = (Text, Maybe (FullList Text))
- class Collectable a where
- collect :: a -> Map CollectedVar Int -> Map CollectedVar Int
- class Idable a where
- anonymiseSingletons :: (Collectable a, DescendGeniVal a) => a -> a
- finaliseVarsById :: (Collectable a, DescendGeniVal a, Idable a) => a -> a
- finaliseVars :: (Collectable a, DescendGeniVal a) => Text -> a -> a
- crushOne :: [GeniVal] -> Maybe GeniVal
- crushList :: [[GeniVal]] -> Maybe [GeniVal]
- class DescendGeniVal a where
- descendGeniVal :: (GeniVal -> GeniVal) -> a -> a
Documentation
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] |
mkGConstNone :: Text -> GeniValSource
mkGVarNone :: Text -> GeniValSource
singletonVal :: GeniVal -> Maybe TextSource
prettySubst :: Subst -> TextSource
allSubsume :: Monad m => [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst)Source
l1 returns the result of allSubsume l2l1 if
doing a simultaneous traversal of both lists, each item in
unify l2l1 subsumes the corresponding item in l2
unifyHelper :: Monad m => (GeniVal -> GeniVal -> UnificationResult) -> [GeniVal] -> [GeniVal] -> m ([GeniVal], Subst)Source
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!
prependToSubst :: (Text, 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 Text GeniVal | |
| SuccessRep2 Text Text GeniVal | |
| Failure |
unifyOne :: GeniVal -> GeniVal -> UnificationResultSource
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
subsumeOne :: GeniVal -> GeniVal -> UnificationResultSource
subsumeOne x y returns the same result as unifyOne x y if x
subsumes y or Failure otherwise
replace :: DescendGeniVal a => Subst -> a -> aSource
replaceOne :: DescendGeniVal a => (Text, GeniVal) -> a -> aSource
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)
replaceMapG :: Subst -> GeniVal -> GeniValSource
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.
Methods
collect :: a -> Map CollectedVar Int -> Map CollectedVar IntSource
Instances
| Collectable GeniVal | |
| Collectable LexEntry | |
| Collectable TagElem | |
| Collectable UninflectedDisjunction | |
| Collectable a => Collectable [a] | |
| Collectable a => Collectable (Maybe a) | |
| Collectable a => Collectable (Tree a) | |
| Collectable a => Collectable (AvPair a) | |
| Collectable a => Collectable (Literal a) | |
| Collectable gv => Collectable (GNode gv) | |
| Collectable a => Collectable (Ttree a) |
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.
anonymiseSingletons :: (Collectable a, DescendGeniVal a) => a -> aSource
Anonymise any variable that occurs only once in the object
finaliseVarsById :: (Collectable a, DescendGeniVal a, Idable a) => a -> aSource
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
class DescendGeniVal a whereSource
Methods
descendGeniVal :: (GeniVal -> GeniVal) -> a -> aSource
Instances
| DescendGeniVal GeniVal | |
| DescendGeniVal LexEntry | |
| DescendGeniVal TagElem | |
| DescendGeniVal TagSite | |
| DescendGeniVal UninflectedDisjunction | |
| DescendGeniVal SimpleItem | |
| (Functor f, DescendGeniVal a) => DescendGeniVal (f a) | |
| DescendGeniVal v => DescendGeniVal (AvPair v) | |
| DescendGeniVal a => DescendGeniVal (Literal a) | |
| DescendGeniVal v => DescendGeniVal (GNode v) | |
| DescendGeniVal v => DescendGeniVal (Ttree v) | |
| DescendGeniVal v => DescendGeniVal ([String], Flist v) | |
| DescendGeniVal a => DescendGeniVal (String, a) | |
| DescendGeniVal (Text, UninflectedDisjunction) | |
| DescendGeniVal a => DescendGeniVal (Map k a) |