Maintainer | Benedikt Schmidt <beschmi@gmail.com> |
---|---|
Safe Haskell | None |
AC unification based on maude and free unification.
- unifyLTerm :: (IsConst c, Show (Lit c LVar), Ord c) => (c -> LSort) -> [Equal (LTerm c)] -> WithMaude [SubstVFresh c LVar]
- unifyLNTerm :: [Equal LNTerm] -> WithMaude [SubstVFresh Name LVar]
- unifiableLNTerms :: LNTerm -> LNTerm -> WithMaude Bool
- unifyLTermFactored :: (IsConst c, Show (Lit c LVar), Ord c) => (c -> LSort) -> [Equal (LTerm c)] -> WithMaude (LSubst c, [SubstVFresh c LVar])
- unifyLNTermFactored :: [Equal LNTerm] -> WithMaude (LNSubst, [SubstVFresh Name LVar])
- matchLVar :: LVar -> LVar -> Match (LTerm c)
- solveMatchLTerm :: (IsConst c, Show (Lit c LVar), Ord c) => (c -> LSort) -> Match (LTerm c) -> WithMaude [Subst c LVar]
- solveMatchLNTerm :: Match LNTerm -> WithMaude [Subst Name LVar]
- data MaudeHandle
- type WithMaude = Reader MaudeHandle
- startMaude :: FilePath -> MaudeSig -> IO MaudeHandle
- getMaudeStats :: MaudeHandle -> IO String
- mhMaudeSig :: MaudeHandle -> MaudeSig
- mhFilePath :: MaudeHandle -> FilePath
- data MaudeSig
- enableDH :: MaudeSig -> Bool
- enableXor :: MaudeSig -> Bool
- enableMSet :: MaudeSig -> Bool
- minimalMaudeSig :: MaudeSig
- dhMaudeSig, msetMaudeSig, xorMaudeSig :: MaudeSig
- pairMaudeSig, hashMaudeSig, signatureMaudeSig, asymEncMaudeSig, symEncMaudeSig :: MaudeSig
- rrulesForMaudeSig :: MaudeSig -> Set (RRule LNTerm)
- allFunctionSymbols :: MaudeSig -> Set NonACSym
- stRules :: MaudeSig -> Set StRule
- irreducibleFunctionSymbols :: MaudeSig -> Set NonACSym
- addFunctionSymbol :: NonACSym -> MaudeSig -> MaudeSig
- addStRule :: StRule -> MaudeSig -> MaudeSig
- module Term.Substitution
- module Term.Rewriting.Definitions
Unification modulo AC
unifyLTerm :: (IsConst c, Show (Lit c LVar), Ord c) => (c -> LSort) -> [Equal (LTerm c)] -> WithMaude [SubstVFresh c LVar]Source
unifyLNTerm eqs
returns a complete set of unifiers for eqs
modulo AC.
unifyLNTerm :: [Equal LNTerm] -> WithMaude [SubstVFresh Name LVar]Source
unifyLNTerm eqs
returns a complete set of unifiers for eqs
modulo AC.
unifyLTermFactored :: (IsConst c, Show (Lit c LVar), Ord c) => (c -> LSort) -> [Equal (LTerm c)] -> WithMaude (LSubst c, [SubstVFresh c LVar])Source
unifyLTerm sortOf eqs
returns a complete set of unifiers for eqs
modulo AC.
unifyLNTermFactored :: [Equal LNTerm] -> WithMaude (LNSubst, [SubstVFresh Name LVar])Source
unifyLTerm sortOf eqs
returns a complete set of unifiers for eqs
modulo AC.
matching modulo AC
Constructing matching problems
Solving matching problems
solveMatchLTerm :: (IsConst c, Show (Lit c LVar), Ord c) => (c -> LSort) -> Match (LTerm c) -> WithMaude [Subst c LVar]Source
solveMatchLNTerm sortOf eqs
returns a complete set of matchers for
eqs
modulo AC.
solveMatchLNTerm :: Match LNTerm -> WithMaude [Subst Name LVar]Source
solveMatchLNTerm eqs
returns a complete set of matchers for eqs
modulo AC.
Handles to a Maude process
data MaudeHandle Source
A handle to a Maude process. It requires the Maude path for Signatures to be serializable. If we also add the string for the Maude config file, then it would even be serializable on its own.
type WithMaude = Reader MaudeHandleSource
Values that depend on a MaudeHandle
.
startMaude :: FilePath -> MaudeSig -> IO MaudeHandleSource
startMaude
starts a new instance of Maude and returns a Handle to it.
getMaudeStats :: MaudeHandle -> IO StringSource
getMaudeStats
returns the maude stats formatted as a string.
Maude signatures
The required information to define a Maude functional module
.
enableMSet :: MaudeSig -> BoolSource
minimalMaudeSig :: MaudeSigSource
The minimal maude signature.
dhMaudeSig, msetMaudeSig, xorMaudeSig :: MaudeSigSource
Maude signatures for the AC symbols.
pairMaudeSig, hashMaudeSig, signatureMaudeSig, asymEncMaudeSig, symEncMaudeSig :: MaudeSigSource
Maude signatures for the default subterm symbols.
rrulesForMaudeSig :: MaudeSig -> Set (RRule LNTerm)Source
rrulesForMaudeSig msig
returns all rewriting rules including the rules
for xor, dh, and multiset.
allFunctionSymbols :: MaudeSig -> Set NonACSymSource
function signature including the nonAC function symbols for DH, Xor, and MSet can be computed from enableX and functionSymbols
addFunctionSymbol :: NonACSym -> MaudeSig -> MaudeSigSource
Add function symbol to given maude signature.
Convenience exports
module Term.Substitution
module Term.Rewriting.Definitions