twee-lib-2.3: An equational theorem prover
Safe HaskellNone
LanguageHaskell2010

Twee

Description

The main prover loop.

Synopsis

Configuration and prover state.

defaultConfig :: Config f Source #

The default prover configuration.

configIsComplete :: Config f -> Bool Source #

Does this configuration run the prover in a complete mode?

initialState :: Config f -> State f Source #

The initial state.

Messages.

data Message f Source #

A message which is produced by the prover when something interesting happens.

Constructors

NewActive !(Active f)

A new rule.

NewEquation !(Equation f)

A new joinable equation.

DeleteActive !(Active f)

A rule was deleted.

SimplifyQueue

The CP queue was simplified.

NotComplete !IntSet

All except these axioms are complete (with a suitable-chosen subset of the rules).

Interreduce

The rules were reduced wrt each other.

Status !Int

Status update: how many queued critical pairs there are.

Instances

Instances details
Function f => Pretty (Message f) Source # 
Instance details

Defined in Twee

message :: PrettyTerm f => Message f -> State f -> State f Source #

Emit a message.

clearMessages :: State f -> State f Source #

Forget about all emitted messages.

messages :: State f -> [Message f] Source #

Get all emitted messages.

The CP queue.

data Params Source #

Instances

Instances details
Params Params Source # 
Instance details

Defined in Twee

type Score Params Source # 
Instance details

Defined in Twee

type Id Params Source # 
Instance details

Defined in Twee

type PackedScore Params Source # 
Instance details

Defined in Twee

type PackedId Params Source # 
Instance details

Defined in Twee

makePassives :: Function f => Config f -> State f -> ActiveRule f -> [Passive Params] Source #

Compute all critical pairs from a rule.

findPassive :: forall f. Function f => State f -> Passive Params -> Maybe (ActiveRule f, ActiveRule f, Overlap f) Source #

Turn a Passive back into an overlap. Doesn't try to simplify it.

simplifyPassive :: Function f => Config f -> State f -> Passive Params -> Maybe (Passive Params) Source #

Renormalise a queued Passive.

shouldSimplifyQueue :: Function f => Config f -> State f -> Bool Source #

Check if we should renormalise the queue.

simplifyQueue :: Function f => Config f -> State f -> State f Source #

Renormalise the entire queue.

enqueue :: Function f => State f -> RuleId -> [Passive Params] -> State f Source #

Enqueue a set of critical pairs.

dequeue :: Function f => Config f -> State f -> (Maybe (CriticalPair f, ActiveRule f, ActiveRule f), State f) Source #

Dequeue a critical pair.

Also takes care of:

  • removing any orphans from the head of the queue
  • ignoring CPs that are too big

Active rewrite rules.

data Active f Source #

Constructors

Active 

Instances

Instances details
Eq (Active f) Source # 
Instance details

Defined in Twee

Methods

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

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

Function f => Pretty (Active f) Source # 
Instance details

Defined in Twee

data ActiveRule f Source #

Constructors

ActiveRule 

Instances

Instances details
Eq (ActiveRule f) Source # 
Instance details

Defined in Twee

Methods

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

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

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

Defined in Twee

Associated Types

type ConstantOf (ActiveRule f) Source #

Has (ActiveRule f) Max Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Max 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 (ActiveRule f) (Positions g) Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> Positions g Source #

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

Defined in Twee

Methods

the :: ActiveRule f -> Rule g Source #

type ConstantOf (ActiveRule f) Source # 
Instance details

Defined in Twee

type ConstantOf (ActiveRule f) = f

newtype RuleId Source #

Constructors

RuleId Id 

Instances

Instances details
Enum RuleId Source # 
Instance details

Defined in Twee

Eq RuleId Source # 
Instance details

Defined in Twee

Methods

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

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

Integral RuleId Source # 
Instance details

Defined in Twee

Num RuleId Source # 
Instance details

Defined in Twee

Ord RuleId Source # 
Instance details

Defined in Twee

Real RuleId Source # 
Instance details

Defined in Twee

Show RuleId Source # 
Instance details

Defined in Twee

Has (ActiveRule f) RuleId Source # 
Instance details

Defined in Twee

Methods

the :: ActiveRule f -> RuleId Source #

addActive :: Function f => Config f -> State f -> (Id -> RuleId -> RuleId -> Active f) -> State f Source #

sample :: Function f => Config f -> Int -> [Passive Params] -> State f -> State f Source #

addCP :: Function f => Config f -> Model f -> State f -> CriticalPair f -> State f Source #

addAxiom :: Function f => Config f -> State f -> Axiom f -> State f Source #

data Goal f Source #

Instances

Instances details
(Labelled f, Show f) => Show (Goal f) Source # 
Instance details

Defined in Twee

Methods

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

show :: Goal f -> String #

showList :: [Goal f] -> ShowS #

addGoal :: Function f => Config f -> State f -> Goal f -> State f Source #

goal :: Int -> String -> Equation f -> Goal f Source #

data Output m f Source #

Constructors

Output 

Fields

complete :: (Function f, MonadIO m) => Output m f -> Config f -> State f -> m (State f) Source #

complete1 :: Function f => Config f -> State f -> (Bool, State f) Source #

rules :: Function f => State f -> [Rule f] Source #

normalForms :: Function f => State f -> Term f -> Map (Term f) (Reduction f) Source #