twee-lib-2.2: An equational theorem prover

Safe HaskellNone
LanguageHaskell2010

Twee.Base

Contents

Description

Useful operations on terms and similar. Also re-exports some generally useful modules such as Term and Pretty.

Synopsis

Re-exported functionality

data Builder f Source #

A monoid for building terms. mempty represents the empty termlist, while mappend appends two termlists.

Instances
Semigroup (Builder f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

(<>) :: Builder f -> Builder f -> Builder f #

sconcat :: NonEmpty (Builder f) -> Builder f #

stimes :: Integral b => b -> Builder f -> Builder f #

Monoid (Builder f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

mempty :: Builder f #

mappend :: Builder f -> Builder f -> Builder f #

mconcat :: [Builder f] -> Builder f #

Build (Builder f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type BuildFun (Builder f) :: Type Source #

type BuildFun (Builder f) Source # 
Instance details

Defined in Twee.Term

type BuildFun (Builder f) = f

newtype Var Source #

A variable.

Constructors

V 

Fields

  • var_id :: Int

    The variable's number. Don't use huge variable numbers: they will be truncated to 32 bits when stored in a term.

Instances
Enum Var Source # 
Instance details

Defined in Twee.Term.Core

Methods

succ :: Var -> Var #

pred :: Var -> Var #

toEnum :: Int -> Var #

fromEnum :: Var -> Int #

enumFrom :: Var -> [Var] #

enumFromThen :: Var -> Var -> [Var] #

enumFromTo :: Var -> Var -> [Var] #

enumFromThenTo :: Var -> Var -> Var -> [Var] #

Eq Var Source # 
Instance details

Defined in Twee.Term.Core

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Ord Var Source # 
Instance details

Defined in Twee.Term.Core

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Show Var Source # 
Instance details

Defined in Twee.Term.Core

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Pretty Var Source # 
Instance details

Defined in Twee.Pretty

data Fun f Source #

A function symbol. f is the underlying type of function symbols defined by the user; Fun f is an f together with an automatically-generated unique number.

Instances
Eq (Fun f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

(==) :: Fun f -> Fun f -> Bool #

(/=) :: Fun f -> Fun f -> Bool #

Ord (Fun f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

compare :: Fun f -> Fun f -> Ordering #

(<) :: Fun f -> Fun f -> Bool #

(<=) :: Fun f -> Fun f -> Bool #

(>) :: Fun f -> Fun f -> Bool #

(>=) :: Fun f -> Fun f -> Bool #

max :: Fun f -> Fun f -> Fun f #

min :: Fun f -> Fun f -> Fun f #

Show (Fun f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

showsPrec :: Int -> Fun f -> ShowS #

show :: Fun f -> String #

showList :: [Fun f] -> ShowS #

Pretty f => Pretty (Fun f) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Fun f -> Doc #

pPrint :: Fun f -> Doc #

pPrintList :: PrettyLevel -> [Fun f] -> Doc #

PrettyTerm f => PrettyTerm (Fun f) Source # 
Instance details

Defined in Twee.Pretty

Methods

termStyle :: Fun f -> TermStyle Source #

EqualsBonus f => EqualsBonus (Fun f) Source # 
Instance details

Defined in Twee.Base

Sized f => Sized (Fun f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: Fun f -> Int Source #

Arity f => Arity (Fun f) Source # 
Instance details

Defined in Twee.Base

Methods

arity :: Fun f -> Int Source #

data Term f Source #

Term f is a term whose function symbols have type f. It is either a Var or an App.

Instances
Eq (Term f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

(==) :: Term f -> Term f -> Bool #

(/=) :: Term f -> Term f -> Bool #

Ord (Term f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

compare :: Term f -> Term f -> Ordering #

(<) :: Term f -> Term f -> Bool #

(<=) :: Term f -> Term f -> Bool #

(>) :: Term f -> Term f -> Bool #

(>=) :: Term f -> Term f -> Bool #

max :: Term f -> Term f -> Term f #

min :: Term f -> Term f -> Term f #

Show (Term f) Source # 
Instance details

Defined in Twee.Term

Methods

showsPrec :: Int -> Term f -> ShowS #

show :: Term f -> String #

showList :: [Term f] -> ShowS #

PrettyTerm f => Pretty (Term f) Source # 
Instance details

Defined in Twee.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Term f -> Doc #

pPrint :: Term f -> Doc #

pPrintList :: PrettyLevel -> [Term f] -> Doc #

Build (Term f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type BuildFun (Term f) :: Type Source #

Methods

builder :: Term f -> Builder (BuildFun (Term f)) Source #

Sized f => Sized (Term f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: Term f -> Int Source #

Symbolic (Term f) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (Term f) :: Type Source #

Methods

termsDL :: Term f -> DList (TermListOf (Term f)) Source #

subst_ :: (Var -> BuilderOf (Term f)) -> Term f -> Term f Source #

f ~ g => Has (Rule f) (Term g) Source # 
Instance details

Defined in Twee.Rule

Methods

the :: Rule f -> Term g Source #

type BuildFun (Term f) Source # 
Instance details

Defined in Twee.Term

type BuildFun (Term f) = f
type ConstantOf (Term f) Source # 
Instance details

Defined in Twee.Base

type ConstantOf (Term f) = f

data TermList f Source #

TermList f is a list of terms whose function symbols have type f. It is either a Cons or an Empty. You can turn it into a [Term f] with unpack.

Instances
Eq (TermList f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

(==) :: TermList f -> TermList f -> Bool #

(/=) :: TermList f -> TermList f -> Bool #

Ord (TermList f) Source # 
Instance details

Defined in Twee.Term.Core

Methods

compare :: TermList f -> TermList f -> Ordering #

(<) :: TermList f -> TermList f -> Bool #

(<=) :: TermList f -> TermList f -> Bool #

(>) :: TermList f -> TermList f -> Bool #

(>=) :: TermList f -> TermList f -> Bool #

max :: TermList f -> TermList f -> TermList f #

min :: TermList f -> TermList f -> TermList f #

Show (TermList f) Source # 
Instance details

Defined in Twee.Term

Methods

showsPrec :: Int -> TermList f -> ShowS #

show :: TermList f -> String #

showList :: [TermList f] -> ShowS #

PrettyTerm f => Pretty (TermList f) Source # 
Instance details

Defined in Twee.Pretty

Build (TermList f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type BuildFun (TermList f) :: Type Source #

Sized f => Sized (TermList f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: TermList f -> Int Source #

Symbolic (TermList f) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (TermList f) :: Type Source #

type BuildFun (TermList f) Source # 
Instance details

Defined in Twee.Term

type BuildFun (TermList f) = f
type ConstantOf (TermList f) Source # 
Instance details

Defined in Twee.Base

type ConstantOf (TermList f) = f

pattern App :: Fun f -> TermList f -> Term f Source #

Matches a function application.

pattern Var :: Var -> Term f Source #

Matches a variable.

pattern UnsafeConsSym :: Term 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.

pattern ConsSym :: Term 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 Cons :: Term f -> TermList f -> TermList f Source #

Matches a non-empty termlist, unpacking it into head and tail.

pattern Empty :: TermList f Source #

Matches the empty termlist.

at :: Int -> TermList f -> Term f Source #

Index into a termlist.

lenList :: TermList f -> Int Source #

The length of (number of symbols in) a termlist.

fun :: (Ord f, Typeable f) => f -> Fun f Source #

Construct a Fun from a function symbol.

fun_value :: Fun f -> f Source #

The underlying function symbol of a Fun.

singleton :: Term f -> TermList f Source #

Convert a term to a termlist.

isSubtermOfList :: Term f -> TermList f -> Bool Source #

Is a term contained as a subterm in a given termlist?

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
Show (TriangleSubst f) Source # 
Instance details

Defined in Twee.Term

Substitution (TriangleSubst f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type SubstFun (TriangleSubst f) :: Type Source #

type SubstFun (TriangleSubst f) Source # 
Instance details

Defined in Twee.Term

type SubstFun (TriangleSubst f) = f

newtype Subst f Source #

A substitution which maps variables to terms of type Term f.

Constructors

Subst 

Fields

Instances
Eq (Subst f) Source # 
Instance details

Defined in Twee.Term

Methods

(==) :: Subst f -> Subst f -> Bool #

(/=) :: Subst f -> Subst f -> Bool #

Show (Subst f) Source # 
Instance details

Defined in Twee.Term

Methods

showsPrec :: Int -> Subst f -> ShowS #

show :: Subst f -> String #

showList :: [Subst f] -> ShowS #

PrettyTerm f => Pretty (Subst f) Source # 
Instance details

Defined in Twee.Pretty

Substitution (Subst f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type SubstFun (Subst f) :: Type Source #

Symbolic (Subst f) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (Subst f) :: Type Source #

Methods

termsDL :: Subst f -> DList (TermListOf (Subst f)) Source #

subst_ :: (Var -> BuilderOf (Subst f)) -> Subst f -> Subst f Source #

type SubstFun (Subst f) Source # 
Instance details

Defined in Twee.Term

type SubstFun (Subst f) = f
type ConstantOf (Subst f) Source # 
Instance details

Defined in Twee.Base

type ConstantOf (Subst f) = f

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

evalSubst

Associated Types

type SubstFun s Source #

The underlying type of function symbols.

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 (TriangleSubst f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type SubstFun (TriangleSubst f) :: Type Source #

Substitution (Subst f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type SubstFun (Subst f) :: Type Source #

(Build a, v ~ Var) => Substitution (v -> a) Source # 
Instance details

Defined in Twee.Term

Associated Types

type SubstFun (v -> a) :: Type Source #

Methods

evalSubst :: (v -> a) -> Var -> Builder (SubstFun (v -> a)) Source #

substList :: (v -> a) -> TermList (SubstFun (v -> a)) -> Builder (SubstFun (v -> a)) Source #

class Build a where Source #

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.

Associated Types

type BuildFun a Source #

The underlying type of function symbols.

Methods

builder :: a -> Builder (BuildFun a) Source #

Convert a value into a Builder.

Instances
Build a => Build [a] Source # 
Instance details

Defined in Twee.Term

Associated Types

type BuildFun [a] :: Type Source #

Methods

builder :: [a] -> Builder (BuildFun [a]) Source #

Build (Builder f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type BuildFun (Builder f) :: Type Source #

Build (Term f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type BuildFun (Term f) :: Type Source #

Methods

builder :: Term f -> Builder (BuildFun (Term f)) Source #

Build (TermList f) Source # 
Instance details

Defined in Twee.Term

Associated Types

type BuildFun (TermList f) :: Type Source #

pattern F :: f -> Fun f Source #

A pattern which extracts the fun_value from a Fun.

build :: Build a => a -> Term (BuildFun a) Source #

Build a term. The given builder must produce exactly one term.

buildList :: Build a => a -> TermList (BuildFun a) Source #

Build a termlist.

con :: Fun f -> Builder f Source #

Build a constant (a function with no arguments).

app :: Build a => Fun (BuildFun a) -> a -> Builder (BuildFun a) Source #

Build a function application.

var :: Var -> Builder f Source #

Build a variable.

substToList :: Subst f -> [(Var, Term f)] Source #

Convert a substitution to a list of bindings.

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.

substSize :: Subst f -> Int Source #

Return the highest-number variable in a substitution plus 1.

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.

retract :: Var -> Subst f -> Subst f Source #

Remove a binding from a substitution.

unsafeExtendList :: Var -> TermList f -> Subst f -> Subst f Source #

Add a new binding to a substitution. Overwrites any existing binding.

substCompose :: Substitution s => Subst (SubstFun s) -> s -> Subst (SubstFun s) Source #

Compose two substitutions.

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.

close :: TriangleSubst f -> Subst f Source #

Iterate a triangle substitution to make it idempotent.

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.

match :: Term f -> Term f -> Maybe (Subst f) Source #

match pat t matches the term t 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.

unify :: Term f -> Term f -> Maybe (Subst f) Source #

Unify two terms.

unifyList :: TermList f -> TermList f -> Maybe (Subst f) Source #

Unify two termlists.

unifyTri :: Term f -> Term f -> Maybe (TriangleSubst f) Source #

Unify two terms, returning a triangle substitution. This is slightly faster than unify.

unifyListTri :: TermList f -> TermList f -> Maybe (TriangleSubst f) Source #

Unify two termlists, returning a triangle substitution. This is slightly faster than unify.

empty :: forall f. TermList f Source #

The empty termlist.

children :: Term f -> TermList f Source #

Get the children (direct subterms) of a term.

unpack :: TermList f -> [Term f] Source #

Convert a termlist into an ordinary list of terms.

lookup :: Var -> Subst f -> Maybe (Term f) Source #

Look up a variable in a substitution.

extend :: Var -> Term f -> Subst f -> Maybe (Subst f) Source #

Add a new binding to a substitution.

len :: Term f -> Int Source #

Find the length of a term.

bound :: Term f -> (Var, Var) Source #

Return the lowest- and highest-numbered variables in a term.

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.

occurs :: Var -> Term f -> Bool Source #

Check if a variable occurs in a term.

subtermsList :: TermList f -> [Term f] Source #

Find all subterms of a termlist.

subterms :: Term f -> [Term f] Source #

Find all subterms of a term.

properSubterms :: Term f -> [Term f] Source #

Find all proper subterms of a term.

isApp :: Term f -> Bool Source #

Check if a term is a function application.

isVar :: Term f -> Bool Source #

Check if a term is a variable

isInstanceOf :: Term f -> Term f -> Bool Source #

t `'isInstanceOf'\` pat checks if t is an instance of pat.

isVariantOf :: Term f -> Term f -> Bool Source #

Check if two terms are renamings of one another.

isSubtermOf :: Term f -> Term f -> Bool Source #

Is a term a subterm of another one?

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.

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.

positionToPath :: Term f -> Int -> [Int] Source #

Convert a position in a term, expressed as a single number, into a path.

pathToPosition :: Term f -> [Int] -> Int Source #

Convert a path in a term into a position.

(<<) :: Ord f => Fun f -> Fun f -> Bool Source #

Compare the fun_values of two Funs.

The Symbolic typeclass

class Symbolic a where Source #

Generalisation of term functionality to things that contain terms (e.g., rewrite rules and equations).

Associated Types

type ConstantOf a Source #

Methods

termsDL :: a -> DList (TermListOf a) Source #

Compute a DList of all terms which appear in the argument (used for e.g. computing free variables). See also terms.

subst_ :: (Var -> BuilderOf a) -> a -> a Source #

Apply a substitution. When using the Symbolic type class, you can use subst instead.

Instances
Symbolic a => Symbolic [a] Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf [a] :: Type Source #

Methods

termsDL :: [a] -> DList (TermListOf [a]) Source #

subst_ :: (Var -> BuilderOf [a]) -> [a] -> [a] Source #

Symbolic a => Symbolic (Maybe a) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (Maybe a) :: Type Source #

Methods

termsDL :: Maybe a -> DList (TermListOf (Maybe a)) Source #

subst_ :: (Var -> BuilderOf (Maybe a)) -> Maybe a -> Maybe a Source #

Symbolic (Term f) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (Term f) :: Type Source #

Methods

termsDL :: Term f -> DList (TermListOf (Term f)) Source #

subst_ :: (Var -> BuilderOf (Term f)) -> Term f -> Term f Source #

Symbolic (TermList f) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (TermList f) :: Type Source #

Symbolic (Subst f) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (Subst f) :: Type Source #

Methods

termsDL :: Subst f -> DList (TermListOf (Subst f)) Source #

subst_ :: (Var -> BuilderOf (Subst f)) -> Subst f -> Subst f Source #

Symbolic (Equation f) Source # 
Instance details

Defined in Twee.Equation

Associated Types

type ConstantOf (Equation f) :: Type Source #

Symbolic (Derivation f) Source # 
Instance details

Defined in Twee.Proof

Associated Types

type ConstantOf (Derivation f) :: Type Source #

Symbolic (Resulting f) Source # 
Instance details

Defined in Twee.Rule

Associated Types

type ConstantOf (Resulting f) :: Type Source #

Symbolic (Reduction f) Source # 
Instance details

Defined in Twee.Rule

Associated Types

type ConstantOf (Reduction f) :: Type Source #

Symbolic (Orientation f) Source # 
Instance details

Defined in Twee.Rule

Associated Types

type ConstantOf (Orientation f) :: Type Source #

Symbolic (Rule f) Source # 
Instance details

Defined in Twee.Rule

Associated Types

type ConstantOf (Rule f) :: Type Source #

Methods

termsDL :: Rule f -> DList (TermListOf (Rule f)) Source #

subst_ :: (Var -> BuilderOf (Rule f)) -> Rule f -> Rule f Source #

Symbolic (CriticalPair f) Source # 
Instance details

Defined in Twee.CP

Associated Types

type ConstantOf (CriticalPair f) :: Type Source #

PrettyTerm f => Symbolic (ActiveRule f) Source # 
Instance details

Defined in Twee

Associated Types

type ConstantOf (ActiveRule f) :: Type Source #

(ConstantOf a ~ ConstantOf b, Symbolic a, Symbolic b) => Symbolic (a, b) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (a, b) :: Type Source #

Methods

termsDL :: (a, b) -> DList (TermListOf (a, b)) Source #

subst_ :: (Var -> BuilderOf (a, b)) -> (a, b) -> (a, b) Source #

(ConstantOf a ~ ConstantOf b, ConstantOf a ~ ConstantOf c, Symbolic a, Symbolic b, Symbolic c) => Symbolic (a, b, c) Source # 
Instance details

Defined in Twee.Base

Associated Types

type ConstantOf (a, b, c) :: Type Source #

Methods

termsDL :: (a, b, c) -> DList (TermListOf (a, b, c)) Source #

subst_ :: (Var -> BuilderOf (a, b, c)) -> (a, b, c) -> (a, b, c) Source #

subst :: (Symbolic a, Substitution s, SubstFun s ~ ConstantOf a) => s -> a -> a Source #

Apply a substitution.

terms :: Symbolic a => a -> [TermListOf a] Source #

Find all terms occuring in the argument.

type TermOf a = Term (ConstantOf a) Source #

A term compatible with a given Symbolic.

type TermListOf a = TermList (ConstantOf a) Source #

A termlist compatible with a given Symbolic.

type SubstOf a = Subst (ConstantOf a) Source #

A substitution compatible with a given Symbolic.

type TriangleSubstOf a = TriangleSubst (ConstantOf a) Source #

A triangle substitution compatible with a given Symbolic.

type BuilderOf a = Builder (ConstantOf a) Source #

A builder compatible with a given Symbolic.

type FunOf a = Fun (ConstantOf a) Source #

The underlying type of function symbols of a given Symbolic.

vars :: Symbolic a => a -> [Var] Source #

Find the variables occurring in the argument.

isGround :: Symbolic a => a -> Bool Source #

Test if the argument is ground.

funs :: Symbolic a => a -> [FunOf a] Source #

Find the function symbols occurring in the argument.

occ :: Symbolic a => FunOf a -> a -> Int Source #

Count how many times a function symbol occurs in the argument.

occVar :: Symbolic a => Var -> a -> Int Source #

Count how many times a variable occurs in the argument.

canonicalise :: Symbolic a => a -> a Source #

Rename the argument so that variables are introduced in a canonical order (starting with V0, then V1 and so on).

renameAvoiding :: (Symbolic a, Symbolic b) => a -> b -> b Source #

Rename the second argument so that it does not mention any variable which occurs in the first.

General-purpose functionality

newtype Id Source #

Represents a unique identifier (e.g., for a rule).

Constructors

Id 

Fields

Instances
Bounded Id Source # 
Instance details

Defined in Twee.Base

Methods

minBound :: Id #

maxBound :: Id #

Enum Id Source # 
Instance details

Defined in Twee.Base

Methods

succ :: Id -> Id #

pred :: Id -> Id #

toEnum :: Int -> Id #

fromEnum :: Id -> Int #

enumFrom :: Id -> [Id] #

enumFromThen :: Id -> Id -> [Id] #

enumFromTo :: Id -> Id -> [Id] #

enumFromThenTo :: Id -> Id -> Id -> [Id] #

Eq Id Source # 
Instance details

Defined in Twee.Base

Methods

(==) :: Id -> Id -> Bool #

(/=) :: Id -> Id -> Bool #

Integral Id Source # 
Instance details

Defined in Twee.Base

Methods

quot :: Id -> Id -> Id #

rem :: Id -> Id -> Id #

div :: Id -> Id -> Id #

mod :: Id -> Id -> Id #

quotRem :: Id -> Id -> (Id, Id) #

divMod :: Id -> Id -> (Id, Id) #

toInteger :: Id -> Integer #

Num Id Source # 
Instance details

Defined in Twee.Base

Methods

(+) :: Id -> Id -> Id #

(-) :: Id -> Id -> Id #

(*) :: Id -> Id -> Id #

negate :: Id -> Id #

abs :: Id -> Id #

signum :: Id -> Id #

fromInteger :: Integer -> Id #

Ord Id Source # 
Instance details

Defined in Twee.Base

Methods

compare :: Id -> Id -> Ordering #

(<) :: Id -> Id -> Bool #

(<=) :: Id -> Id -> Bool #

(>) :: Id -> Id -> Bool #

(>=) :: Id -> Id -> Bool #

max :: Id -> Id -> Id #

min :: Id -> Id -> Id #

Real Id Source # 
Instance details

Defined in Twee.Base

Methods

toRational :: Id -> Rational #

Show Id Source # 
Instance details

Defined in Twee.Base

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

Pretty Id Source # 
Instance details

Defined in Twee.Base

Has (ActiveRule f) Id Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Id Source #

class Has a b where Source #

An instance Has a b indicates that a value of type a contains a value of type b which is somehow part of the meaning of the a.

A number of functions use Has constraints to work in a more general setting. For example, the functions in CP operate on rewrite rules, but actually accept any a satisfying Has a (Rule f).

Use taste when definining Has instances; don't do it willy-nilly.

Methods

the :: a -> b Source #

Get at the thing.

Instances
Has a a Source # 
Instance details

Defined in Twee.Base

Methods

the :: a -> a Source #

Has (ActiveRule f) Depth Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Depth Source #

Has (ActiveRule f) RuleId Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> RuleId Source #

Has (ActiveRule f) Id Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Id Source #

f ~ g => Has (Rule f) (Term g) Source # 
Instance details

Defined in Twee.Rule

Methods

the :: Rule f -> Term g Source #

f ~ g => Has (ActiveRule f) (Positions g) Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Positions g Source #

f ~ g => Has (ActiveRule f) (Proof g) Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Proof g Source #

f ~ g => Has (ActiveRule f) (Rule g) Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Rule g Source #

Typeclasses

class Minimal f where Source #

Methods

minimal :: Fun f Source #

Instances
(Typeable f, Ord f) => Minimal (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

minimal :: Fun (Extended f) Source #

minimalTerm :: Minimal f => Term f Source #

Build the minimal constant as a term.

isMinimal :: Minimal f => Term f -> Bool Source #

Check if a term is the minimal constant.

erase :: (Symbolic a, ConstantOf a ~ f, Minimal f) => [Var] -> a -> a Source #

Erase a given set of variables from the argument, replacing them with the minimal constant.

class Skolem f where Source #

Construction of Skolem constants.

Methods

skolem :: Var -> Fun f Source #

Turn a variable into a Skolem constant.

getSkolem :: Fun f -> Maybe Var Source #

Instances
(Typeable f, Ord f) => Skolem (Extended f) Source # 
Instance details

Defined in Twee.Base

class Arity f where Source #

For types which have a notion of arity.

Methods

arity :: f -> Int Source #

Measure the arity.

Instances
Arity f => Arity (Fun f) Source # 
Instance details

Defined in Twee.Base

Methods

arity :: Fun f -> Int Source #

Arity f => Arity (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

arity :: Extended f -> Int Source #

class Sized a where Source #

For types which have a notion of size.

Methods

size :: a -> Int Source #

Compute the size.

Instances
Sized f => Sized (Fun f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: Fun f -> Int Source #

Sized f => Sized (Term f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: Term f -> Int Source #

Sized f => Sized (TermList f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: TermList f -> Int Source #

Sized f => Sized (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: Extended f -> Int Source #

Sized f => Sized (Equation f) Source # 
Instance details

Defined in Twee.Equation

Methods

size :: Equation f -> Int Source #

class Ord f => Ordered f where Source #

Methods

lessEq :: Term f -> Term f -> Bool Source #

Return True if the first term is less than or equal to the second, in the term ordering.

lessIn :: Model f -> Term f -> Term f -> Maybe Strictness Source #

Check if the first term is less than or equal to the second in the given model, and decide whether the inequality is strict or nonstrict.

lessThan :: Ordered f => Term f -> Term f -> Bool Source #

Return True if the first argument is strictly less than the second, in the term ordering.

orientTerms :: Ordered f => Term f -> Term f -> Maybe Ordering Source #

Return the direction in which the terms are oriented according to the term ordering, or Nothing if they cannot be oriented. A result of Just LT means that the first term is less than or equal to the second.

class EqualsBonus f where Source #

A hack for encoding Horn clauses. See Score. The default implementation of hasEqualsBonus should work OK.

Minimal complete definition

Nothing

Instances
EqualsBonus f => EqualsBonus (Fun f) Source # 
Instance details

Defined in Twee.Base

EqualsBonus f => EqualsBonus (Extended f) Source # 
Instance details

Defined in Twee.Base

data Strictness Source #

Describes whether an inequality is strict or nonstrict.

Constructors

Strict

The first term is strictly less than the second.

Nonstrict

The first term is less than or equal to the second.

Instances
Eq Strictness Source # 
Instance details

Defined in Twee.Constraints

Show Strictness Source # 
Instance details

Defined in Twee.Constraints

type Function f = (Ordered f, Arity f, Sized f, Minimal f, Skolem f, PrettyTerm f, EqualsBonus f) Source #

The collection of constraints which the type of function symbols must satisfy in order to be used by twee.

data Extended f Source #

A function symbol extended with a minimal constant and Skolem functions. Comes equipped with Extended and Skolem instances.

Constructors

Minimal

The minimal constant.

Skolem Var

A Skolem function.

Function f

An ordinary function symbol.

Instances
Functor Extended Source # 
Instance details

Defined in Twee.Base

Methods

fmap :: (a -> b) -> Extended a -> Extended b #

(<$) :: a -> Extended b -> Extended a #

Eq f => Eq (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

(==) :: Extended f -> Extended f -> Bool #

(/=) :: Extended f -> Extended f -> Bool #

Ord f => Ord (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

compare :: Extended f -> Extended f -> Ordering #

(<) :: Extended f -> Extended f -> Bool #

(<=) :: Extended f -> Extended f -> Bool #

(>) :: Extended f -> Extended f -> Bool #

(>=) :: Extended f -> Extended f -> Bool #

max :: Extended f -> Extended f -> Extended f #

min :: Extended f -> Extended f -> Extended f #

Show f => Show (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

showsPrec :: Int -> Extended f -> ShowS #

show :: Extended f -> String #

showList :: [Extended f] -> ShowS #

Pretty f => Pretty (Extended f) Source # 
Instance details

Defined in Twee.Base

PrettyTerm f => PrettyTerm (Extended f) Source # 
Instance details

Defined in Twee.Base

(Typeable f, Ord f) => Minimal (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

minimal :: Fun (Extended f) Source #

EqualsBonus f => EqualsBonus (Extended f) Source # 
Instance details

Defined in Twee.Base

Sized f => Sized (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

size :: Extended f -> Int Source #

Arity f => Arity (Extended f) Source # 
Instance details

Defined in Twee.Base

Methods

arity :: Extended f -> Int Source #

(Typeable f, Ord f) => Skolem (Extended f) Source # 
Instance details

Defined in Twee.Base