| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Twee.Term
Description
Terms and substitutions.
Terms in twee are represented as arrays rather than as an algebraic data
type. This module defines pattern synonyms (App, Var, Cons, Empty)
which means that pattern matching on terms works just as normal.
The pattern synonyms can not be used to create new terms; for that you
have to use a builder interface (Build).
This module also provides:
Synopsis
- data Term f
- pattern Var :: Var -> Term f
- pattern App :: Fun f -> TermList f -> Term f
- isApp :: Term f -> Bool
- isVar :: Term f -> Bool
- singleton :: Term f -> TermList f
- len :: Term f -> Int
- data TermList f
- pattern Empty :: TermList f
- pattern Cons :: Term f -> TermList f -> TermList f
- pattern ConsSym :: Term f -> TermList f -> TermList f -> TermList f
- hd :: TermList f -> Term f
- tl :: TermList f -> TermList f
- rest :: TermList f -> TermList f
- pattern UnsafeCons :: Term f -> TermList f -> TermList f
- pattern UnsafeConsSym :: Term f -> TermList f -> TermList f -> TermList f
- uhd :: TermList f -> Term f
- utl :: TermList f -> TermList f
- urest :: TermList f -> TermList f
- empty :: forall f. TermList f
- unpack :: TermList f -> [Term f]
- lenList :: TermList f -> Int
- data Fun f
- fun :: Labelled f => f -> Fun f
- fun_id :: Fun f -> Int
- fun_value :: Labelled f => Fun f -> f
- pattern F :: Labelled f => Int -> f -> Fun f
- newtype Var = V {}
- class Labelled f where
- class Build a where
- data Builder f
- build :: Build a => a -> Term (BuildFun a)
- buildList :: Build a => a -> TermList (BuildFun a)
- con :: Fun f -> Builder f
- app :: Build a => Fun (BuildFun a) -> a -> Builder (BuildFun a)
- var :: Var -> Builder f
- children :: Term f -> TermList f
- properSubterms :: Term f -> [Term f]
- subtermsList :: TermList f -> [Term f]
- subterms :: Term f -> [Term f]
- reverseSubtermsList :: TermList f -> [Term f]
- reverseSubterms :: Term f -> [Term f]
- occurs :: Var -> Term f -> Bool
- isSubtermOf :: Term f -> Term f -> Bool
- isSubtermOfList :: Term f -> TermList f -> Bool
- at :: Int -> TermList f -> Term f
- class Substitution s where
- subst :: Substitution s => s -> Term (SubstFun s) -> Builder (SubstFun s)
- newtype Subst f = Subst {}
- emptySubst :: Subst f
- listToSubst :: [(Var, Term f)] -> Maybe (Subst f)
- substToList :: Subst f -> [(Var, Term f)]
- lookup :: Var -> Subst f -> Maybe (Term f)
- lookupList :: Var -> Subst f -> Maybe (TermList f)
- extend :: Var -> Term f -> Subst f -> Maybe (Subst f)
- extendList :: Var -> TermList f -> Subst f -> Maybe (Subst f)
- unsafeExtendList :: Var -> TermList f -> Subst f -> Subst f
- retract :: Var -> Subst f -> Subst f
- foldSubst :: (Var -> TermList f -> b -> b) -> b -> Subst f -> b
- allSubst :: (Var -> TermList f -> Bool) -> Subst f -> Bool
- substDomain :: Subst f -> [Var]
- substSize :: Subst f -> Int
- substCompatible :: Subst f -> Subst f -> Bool
- substUnion :: Subst f -> Subst f -> Subst f
- idempotent :: Subst f -> Bool
- idempotentOn :: Subst f -> TermList f -> Bool
- canonicalise :: [TermList f] -> Subst f
- match :: Term f -> Term f -> Maybe (Subst f)
- matchIn :: Subst f -> Term f -> Term f -> Maybe (Subst f)
- matchList :: TermList f -> TermList f -> Maybe (Subst f)
- matchListIn :: Subst f -> TermList f -> TermList f -> Maybe (Subst f)
- matchMany :: [Term f] -> [Term f] -> Maybe (Subst f)
- matchManyIn :: Subst f -> [Term f] -> [Term f] -> Maybe (Subst f)
- matchManyList :: [TermList f] -> [TermList f] -> Maybe (Subst f)
- matchManyListIn :: Subst f -> [TermList f] -> [TermList f] -> Maybe (Subst f)
- isInstanceOf :: Term f -> Term f -> Bool
- isVariantOf :: Term f -> Term f -> Bool
- unify :: Term f -> Term f -> Maybe (Subst f)
- unifyList :: TermList f -> TermList f -> Maybe (Subst f)
- unifyMany :: [(Term f, Term f)] -> Maybe (Subst f)
- unifyManyTri :: [(Term f, Term f)] -> Maybe (TriangleSubst f)
- unifyTri :: Term f -> Term f -> Maybe (TriangleSubst f)
- unifyTriFrom :: Term f -> Term f -> TriangleSubst f -> Maybe (TriangleSubst f)
- unifyListTri :: TermList f -> TermList f -> Maybe (TriangleSubst f)
- unifyListTriFrom :: TermList f -> TermList f -> TriangleSubst f -> Maybe (TriangleSubst f)
- newtype TriangleSubst f = Triangle {
- unTriangle :: Subst f
- emptyTriangleSubst :: TriangleSubst f
- close :: TriangleSubst f -> Subst f
- positionToPath :: Term f -> Int -> [Int]
- pathToPosition :: Term f -> [Int] -> Int
- replacePosition :: (Build a, BuildFun a ~ f) => Int -> a -> TermList f -> Builder f
- replacePositionSub :: (Substitution sub, SubstFun sub ~ f) => sub -> Int -> TermList f -> TermList f -> Builder f
- replace :: (Build a, BuildFun a ~ f) => Term f -> a -> TermList f -> Builder f
- bound :: Term f -> (Var, Var)
- boundList :: TermList f -> (Var, Var)
- boundLists :: [TermList f] -> (Var, Var)
- mapFun :: (Fun f -> Fun g) -> Term f -> Builder g
- mapFunList :: (Fun f -> Fun g) -> TermList f -> Builder g
- (<<) :: (Labelled f, Ord f) => Fun f -> Fun f -> Bool
Terms
Instances
| (Labelled f, Show f) => Show (Term f) Source # | |
| Eq (Term f) Source # | |
| Ord (Term f) Source # | |
| (Labelled f, PrettyTerm f) => Pretty (Term f) Source # | |
Defined in Twee.Pretty Methods pPrintPrec :: PrettyLevel -> Rational -> Term f -> Doc # pPrintList :: PrettyLevel -> [Term f] -> Doc # | |
| Symbolic (Term f) Source # | |
| (Labelled f, Sized f, Weighted f) => Sized (Term f) Source # | |
| Build (Term f) Source # | |
| f ~ g => Has (Rule f) (Term g) Source # | |
| type ConstantOf (Term f) Source # | |
Defined in Twee.Base | |
| type BuildFun (Term f) Source # | |
Termlists
is a list of terms whose function symbols have type TermList ff.
It is either a Cons or an Empty. You can turn it into a [
with Term f]unpack.
Instances
| (Labelled f, Show f) => Show (TermList f) Source # | |
| Eq (TermList f) Source # | |
| Ord (TermList f) Source # | |
| (Labelled f, PrettyTerm f) => Pretty (TermList f) Source # | |
Defined in Twee.Pretty Methods pPrintPrec :: PrettyLevel -> Rational -> TermList f -> Doc # pPrintList :: PrettyLevel -> [TermList f] -> Doc # | |
| Symbolic (TermList f) Source # | |
| (Labelled f, Sized f, Weighted f) => Sized (TermList f) Source # | |
| Build (TermList f) Source # | |
| type ConstantOf (TermList f) Source # | |
Defined in Twee.Base | |
| type BuildFun (TermList f) Source # | |
pattern Cons :: Term f -> TermList f -> TermList f Source #
Matches a non-empty termlist, unpacking it into head and tail.
pattern ConsSym :: Term f -> TermList f -> TermList f -> TermList f Source #
Matches a non-empty termlist, unpacking it into head and everything except the root symbol of the head. Useful for iterating through terms one symbol at a time.
For example, if ts is the termlist [f(x,y), g(z)],
then let ConsSym u us = ts results in the following bindings:
u = f(x,y) us = [x, y, g(z)]
pattern UnsafeCons :: Term f -> TermList f -> TermList f Source #
Like Cons, but does not check that the termlist is non-empty. Use only if
you are sure the termlist is non-empty.
pattern UnsafeConsSym :: Term f -> TermList f -> TermList f -> TermList f Source #
Like ConsSym, but does not check that the termlist is non-empty. Use only
if you are sure the termlist is non-empty.
Function symbols and variables
A function symbol. f is the underlying type of function symbols defined
by the user; is an Fun ff together with an automatically-generated unique number.
Instances
| (Labelled f, Show f) => Show (Fun f) Source # | |
| Eq (Fun f) Source # | |
| Ord (Fun f) Source # | |
| (Pretty f, Labelled f) => Pretty (Fun f) Source # | |
Defined in Twee.Pretty Methods pPrintPrec :: PrettyLevel -> Rational -> Fun f -> Doc # pPrintList :: PrettyLevel -> [Fun f] -> Doc # | |
| (Labelled f, EqualsBonus f) => EqualsBonus (Fun f) Source # | |
| (Labelled f, Sized f) => Sized (Fun f) Source # | |
| (Weighted f, Labelled f) => Weighted (Fun f) Source # | |
A variable.
Constructors
| V | |
Building terms
Instances of Build can be turned into terms using build or buildList,
and turned into term builders using builder. Has instances for terms,
termlists, builders, and Haskell lists.
A monoid for building terms.
mempty represents the empty termlist, while mappend appends two termlists.
build :: Build a => a -> Term (BuildFun a) Source #
Build a term. The given builder must produce exactly one term.
app :: Build a => Fun (BuildFun a) -> a -> Builder (BuildFun a) Source #
Build a function application.
Access to subterms
properSubterms :: Term f -> [Term f] Source #
Find all proper subterms of a term.
subtermsList :: TermList f -> [Term f] Source #
Find all subterms of a termlist.
reverseSubtermsList :: TermList f -> [Term f] Source #
Find all subterms of a term, but in reverse order.
reverseSubterms :: Term f -> [Term f] Source #
isSubtermOfList :: Term f -> TermList f -> Bool Source #
Is a term contained as a subterm in a given termlist?
Substitutions
class Substitution s where Source #
A class for values which act as substitutions.
Instances include Subst as well as functions from variables to terms.
Minimal complete definition
Methods
evalSubst :: s -> Var -> Builder (SubstFun s) Source #
Apply the substitution to a variable.
substList :: s -> TermList (SubstFun s) -> Builder (SubstFun s) Source #
Apply the substitution to a termlist.
Instances
| Substitution (Subst f) Source # | |
| Substitution (TriangleSubst f) Source # | |
Defined in Twee.Term Associated Types type SubstFun (TriangleSubst f) Source # Methods evalSubst :: TriangleSubst f -> Var -> Builder (SubstFun (TriangleSubst f)) Source # substList :: TriangleSubst f -> TermList (SubstFun (TriangleSubst f)) -> Builder (SubstFun (TriangleSubst f)) Source # | |
| (Build a, v ~ Var) => Substitution (v -> a) Source # | |
subst :: Substitution s => s -> Term (SubstFun s) -> Builder (SubstFun s) Source #
Apply a substitution to a term.
A substitution which maps variables to terms of type .Term f
Instances
| (Labelled f, Show f) => Show (Subst f) Source # | |
| Eq (Subst f) Source # | |
| Ord (Subst f) Source # | |
| (Labelled f, PrettyTerm f) => Pretty (Subst f) Source # | |
Defined in Twee.Pretty Methods pPrintPrec :: PrettyLevel -> Rational -> Subst f -> Doc # pPrintList :: PrettyLevel -> [Subst f] -> Doc # | |
| Symbolic (Subst f) Source # | |
| Substitution (Subst f) Source # | |
| type ConstantOf (Subst f) Source # | |
Defined in Twee.Base | |
| type SubstFun (Subst f) Source # | |
Constructing and querying substitutions
emptySubst :: Subst f Source #
The empty substitution.
listToSubst :: [(Var, Term f)] -> Maybe (Subst f) Source #
Construct a substitution from a list.
Returns Nothing if a variable is bound to several different terms.
lookupList :: Var -> Subst f -> Maybe (TermList f) Source #
Look up a variable in a substitution, returning a termlist.
extendList :: Var -> TermList f -> Subst f -> Maybe (Subst f) Source #
Add a new binding to a substitution, giving a termlist.
unsafeExtendList :: Var -> TermList f -> Subst f -> Subst f Source #
Add a new binding to a substitution. Overwrites any existing binding.
Other operations on substitutions
foldSubst :: (Var -> TermList f -> b -> b) -> b -> Subst f -> b Source #
Fold a function over a substitution.
allSubst :: (Var -> TermList f -> Bool) -> Subst f -> Bool Source #
Check if all bindings of a substitution satisfy a given property.
substDomain :: Subst f -> [Var] Source #
Compute the set of variables bound by a substitution.
substCompatible :: Subst f -> Subst f -> Bool Source #
Check if two substitutions are compatible (they do not send the same variable to different terms).
substUnion :: Subst f -> Subst f -> Subst f Source #
Take the union of two substitutions. The substitutions must be compatible, which is not checked.
idempotent :: Subst f -> Bool Source #
Check if a substitution is idempotent (applying it twice has the same effect as applying it once).
idempotentOn :: Subst f -> TermList f -> Bool Source #
Check if a substitution has no effect on a given term.
canonicalise :: [TermList f] -> Subst f Source #
Return a substitution which renames the variables of a list of terms to put them in a canonical order.
Matching
match :: Term f -> Term f -> Maybe (Subst f) Source #
matches the term match pat tt against the pattern pat.
matchIn :: Subst f -> Term f -> Term f -> Maybe (Subst f) Source #
A variant of match which extends an existing substitution.
matchList :: TermList f -> TermList f -> Maybe (Subst f) Source #
A variant of match which works on termlists.
matchListIn :: Subst f -> TermList f -> TermList f -> Maybe (Subst f) Source #
A variant of match which works on termlists
and extends an existing substitution.
matchMany :: [Term f] -> [Term f] -> Maybe (Subst f) Source #
A variant of match which works on lists of terms.
matchManyIn :: Subst f -> [Term f] -> [Term f] -> Maybe (Subst f) Source #
A variant of match which works on lists of terms,
and extends an existing substitution.
matchManyList :: [TermList f] -> [TermList f] -> Maybe (Subst f) Source #
A variant of match which works on lists of termlists.
matchManyListIn :: Subst f -> [TermList f] -> [TermList f] -> Maybe (Subst f) Source #
A variant of match which works on lists of termlists,
and extends an existing substitution.
isInstanceOf :: Term f -> Term f -> Bool Source #
t ` checks if isInstanceOf` patt is an instance of pat.
Unification
unifyManyTri :: [(Term f, Term f)] -> Maybe (TriangleSubst f) Source #
Unify a collection of pairs of terms, returning a triangle substitution.
unifyTri :: Term f -> Term f -> Maybe (TriangleSubst f) Source #
Unify two terms, returning a triangle substitution.
This is slightly faster than unify.
unifyTriFrom :: Term f -> Term f -> TriangleSubst f -> Maybe (TriangleSubst f) Source #
Unify two terms, starting from an existing substitution.
unifyListTri :: TermList f -> TermList f -> Maybe (TriangleSubst f) Source #
Unify two termlists, returning a triangle substitution.
This is slightly faster than unify.
unifyListTriFrom :: TermList f -> TermList f -> TriangleSubst f -> Maybe (TriangleSubst f) Source #
newtype TriangleSubst f Source #
A triangle substitution is one in which variables can be defined in terms of each other, though not in a circular way.
The main use of triangle substitutions is in unification; unifyTri returns
one. A triangle substitution can be converted to an ordinary substitution
with close, or used directly using its Substitution instance.
Constructors
| Triangle | |
Fields
| |
Instances
| (Labelled f, Show f) => Show (TriangleSubst f) Source # | |
Defined in Twee.Term Methods showsPrec :: Int -> TriangleSubst f -> ShowS # show :: TriangleSubst f -> String # showList :: [TriangleSubst f] -> ShowS # | |
| Substitution (TriangleSubst f) Source # | |
Defined in Twee.Term Associated Types type SubstFun (TriangleSubst f) Source # Methods evalSubst :: TriangleSubst f -> Var -> Builder (SubstFun (TriangleSubst f)) Source # substList :: TriangleSubst f -> TermList (SubstFun (TriangleSubst f)) -> Builder (SubstFun (TriangleSubst f)) Source # | |
| type SubstFun (TriangleSubst f) Source # | |
Defined in Twee.Term | |
emptyTriangleSubst :: TriangleSubst f Source #
The empty triangle substitution.
close :: TriangleSubst f -> Subst f Source #
Iterate a triangle substitution to make it idempotent.
Positions in terms
positionToPath :: Term f -> Int -> [Int] Source #
Convert a position in a term, expressed as a single number, into a path.
replacePosition :: (Build a, BuildFun a ~ f) => Int -> a -> TermList f -> Builder f Source #
Replace the term at a given position in a term with a different term.
replacePositionSub :: (Substitution sub, SubstFun sub ~ f) => sub -> Int -> TermList f -> TermList f -> Builder f Source #
Replace the term at a given position in a term with a different term, while simultaneously applying a substitution. Useful for building critical pairs.
Miscellaneous functions
boundList :: TermList f -> (Var, Var) Source #
Return the lowest- and highest-numbered variables in a termlist.
boundLists :: [TermList f] -> (Var, Var) Source #
Return the lowest- and highest-numbered variables in a list of termlists.
mapFun :: (Fun f -> Fun g) -> Term f -> Builder g Source #
Map a function over the function symbols in a term.
mapFunList :: (Fun f -> Fun g) -> TermList f -> Builder g Source #
Map a function over the function symbols in a termlist.