twee-lib-2.1.5: 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

module Twee.Term

The Symbolic typeclass

class Symbolic a where Source #

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

Minimal complete definition

termsDL, subst_

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 # 

Associated Types

type ConstantOf [a] :: * Source #

Methods

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

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

Symbolic a => Symbolic (Maybe a) Source # 

Associated Types

type ConstantOf (Maybe a) :: * Source #

Methods

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

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

Symbolic (Term f) Source # 

Associated Types

type ConstantOf (Term f) :: * Source #

Methods

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

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

Symbolic (TermList f) Source # 

Associated Types

type ConstantOf (TermList f) :: * Source #

Symbolic (Subst f) Source # 

Associated Types

type ConstantOf (Subst f) :: * Source #

Methods

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

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

Symbolic (Equation f) Source # 

Associated Types

type ConstantOf (Equation f) :: * Source #

Symbolic (Derivation f) Source # 

Associated Types

type ConstantOf (Derivation f) :: * Source #

Symbolic (Resulting f) Source # 

Associated Types

type ConstantOf (Resulting f) :: * Source #

Symbolic (Reduction f) Source # 

Associated Types

type ConstantOf (Reduction f) :: * Source #

Symbolic (Orientation f) Source # 
Symbolic (Rule f) Source # 

Associated Types

type ConstantOf (Rule f) :: * Source #

Methods

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

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

Symbolic (CriticalPair f) Source # 
PrettyTerm f => Symbolic (ActiveRule f) Source # 

Associated Types

type ConstantOf (ActiveRule f) :: * Source #

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

Associated Types

type ConstantOf (a, b) :: * 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 # 

Associated Types

type ConstantOf (a, b, c) :: * 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 # 

Methods

minBound :: Id #

maxBound :: Id #

Enum Id Source # 

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 # 

Methods

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

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

Integral Id Source # 

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 # 

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 # 

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 # 

Methods

toRational :: Id -> Rational #

Show Id Source # 

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

Pretty Id Source # 
Has (ActiveRule f) Id Source # 

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.

Minimal complete definition

the

Methods

the :: a -> b Source #

Get at the thing.

Instances

Has a a Source # 

Methods

the :: a -> a Source #

Has (ActiveRule f) Depth Source # 

Methods

the :: ActiveRule f -> Depth Source #

Has (ActiveRule f) RuleId Source # 

Methods

the :: ActiveRule f -> RuleId Source #

Has (ActiveRule f) Id Source # 

Methods

the :: ActiveRule f -> Id Source #

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

Methods

the :: Rule f -> Term g Source #

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

Methods

the :: ActiveRule f -> Positions g Source #

(~) * f g => Has (ActiveRule f) (Lemma g) Source # 

Methods

the :: ActiveRule f -> Lemma g Source #

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

Methods

the :: ActiveRule f -> Proof g Source #

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

Methods

the :: ActiveRule f -> Rule g Source #

Typeclasses

class Minimal f where Source #

Minimal complete definition

minimal

Methods

minimal :: Fun f Source #

Instances

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

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.

Minimal complete definition

skolem, getSkolem

Methods

skolem :: Var -> Fun f Source #

Turn a variable into a Skolem constant.

getSkolem :: Fun f -> Maybe Var Source #

Instances

class Arity f where Source #

For types which have a notion of arity.

Minimal complete definition

arity

Methods

arity :: f -> Int Source #

Measure the arity.

Instances

Arity f => Arity (Fun f) Source # 

Methods

arity :: Fun f -> Int Source #

Arity f => Arity (Extended f) Source # 

Methods

arity :: Extended f -> Int Source #

class Sized a where Source #

For types which have a notion of size.

Minimal complete definition

size

Methods

size :: a -> Int Source #

Compute the size.

Instances

Sized f => Sized (Fun f) Source # 

Methods

size :: Fun f -> Int Source #

Sized f => Sized (Term f) Source # 

Methods

size :: Term f -> Int Source #

Sized f => Sized (TermList f) Source # 

Methods

size :: TermList f -> Int Source #

Sized f => Sized (Extended f) Source # 

Methods

size :: Extended f -> Int Source #

Sized f => Sized (Equation f) Source # 

Methods

size :: Equation f -> Int Source #

class Ord f => Ordered f where Source #

Minimal complete definition

lessEq, lessIn

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.

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.

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 Minimal and Skolem instances.

Constructors

Minimal

The minimal constant.

Skolem Var

A Skolem function.

Function f

An ordinary function symbol.

Instances

Functor Extended Source # 

Methods

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

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

Eq f => Eq (Extended f) Source # 

Methods

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

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

Ord f => Ord (Extended f) Source # 

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 # 

Methods

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

show :: Extended f -> String #

showList :: [Extended f] -> ShowS #

Pretty f => Pretty (Extended f) Source # 
PrettyTerm f => PrettyTerm (Extended f) Source # 
(Typeable * f, Ord f) => Minimal (Extended f) Source # 

Methods

minimal :: Fun (Extended f) Source #

EqualsBonus f => EqualsBonus (Extended f) Source # 
Sized f => Sized (Extended f) Source # 

Methods

size :: Extended f -> Int Source #

Arity f => Arity (Extended f) Source # 

Methods

arity :: Extended f -> Int Source #

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