| Safe Haskell | Safe-Infered |
|---|
NLP.GenI.Semantics
- data Literal gv = Literal {
- lHandle :: gv
- lPredicate :: gv
- lArgs :: [gv]
- type Sem = [Literal GeniVal]
- type LitConstr = (Literal GeniVal, [Text])
- type SemInput = (Sem, Flist GeniVal, [LitConstr])
- emptyLiteral :: Literal GeniVal
- removeConstraints :: SemInput -> SemInput
- sortSem :: Ord a => [Literal a] -> [Literal a]
- compareOnLiteral :: Ord a => Literal a -> Literal a -> Ordering
- sortByAmbiguity :: Sem -> Sem
- class HasConstants a where
- literalCount :: [Literal GeniVal] -> Map Text Int
- boringLiteral :: Literal GeniVal -> Maybe Text
- isInternalHandle :: Text -> Bool
- subsumeSem :: Sem -> Sem -> [(Sem, Subst)]
- subsumeSemH :: Sem -> Sem -> [(Sem, Subst)]
- subsumeLiteral :: Literal GeniVal -> Literal GeniVal -> Maybe (Literal GeniVal, Subst)
- unifySem :: Sem -> Sem -> [(Sem, Subst)]
- unifySemH :: Sem -> Sem -> [(Sem, Subst)]
- unifyLiteral :: Literal GeniVal -> Literal GeniVal -> Maybe (Literal GeniVal, Subst)
Documentation
Constructors
| Literal | |
Fields
| |
Instances
| Typeable1 Literal | |
| Pretty SemInput | |
| Pretty Sem | |
| GeniShow SemInput | |
| GeniShow Sem | |
| Eq gv => Eq (Literal gv) | |
| Data gv => Data (Literal gv) | |
| Ord gv => Ord (Literal gv) | |
| Binary g => Binary (Literal g) | |
| NFData g => NFData (Literal g) | |
| Pretty (Literal GeniVal) | |
| GeniShow (Literal GeniVal) | |
| DescendGeniVal a => DescendGeniVal (Literal a) | |
| Collectable a => Collectable (Literal a) | |
| HasConstants (Literal GeniVal) |
sortByAmbiguity :: Sem -> SemSource
class HasConstants a whereSource
Instances
isInternalHandle :: Text -> BoolSource
subsumeSem :: Sem -> Sem -> [(Sem, Subst)]Source
x returns all the possible ways to unify
subsumeSem yx with some SUBSET of y so that x subsumes y.
If x does NOT subsume y, we return the empty list.