twee-0.1: An equational theorem prover

Safe HaskellNone
LanguageHaskell2010

Twee

Contents

Documentation

addGoals :: [Set (Term f)] -> Twee f -> Twee f Source #

enqueueM :: Function f => Passive f -> State (Twee f) () Source #

data Modelled a Source #

Constructors

Modelled 

Fields

Instances

rulesFor :: Function f => Int -> Twee f -> Frozen (Rule f) Source #

rules :: Function f => Twee f -> Frozen (Rule f) Source #

normaliseIn :: Function f => Twee f -> Model f -> Term f -> Reduction f Source #

normaliseSub :: Function f => Twee f -> Term f -> Term f -> Reduction f Source #

normaliseCPs :: forall f. Function f => State (Twee f) () Source #

optimise :: a -> (a -> [a]) -> (a -> Bool) -> a Source #

interreduce :: Function f => Rule f -> State (Twee f) () Source #

data Critical a Source #

Constructors

Critical 

Fields

Instances

data CritInfo f Source #

Constructors

CritInfo 

Fields

Instances

data CPInfo Source #

Constructors

CPInfo 

Fields

data CP f Source #

Constructors

CP 

Fields

Instances

Eq (CP f) Source # 

Methods

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

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

Ord (CP f) Source # 

Methods

compare :: CP f -> CP f -> Ordering #

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

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

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

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

max :: CP f -> CP f -> CP f #

min :: CP f -> CP f -> CP f #

Show f => Show (CP f) Source # 

Methods

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

show :: CP f -> String #

showList :: [CP f] -> ShowS #

(Numbered f, PrettyTerm f) => Pretty (CP f) Source # 

Methods

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

pPrint :: CP f -> Doc #

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

Labels (CP f) Source # 

Methods

labels :: CP f -> [Label] Source #

data CPs f Source #

Constructors

CPs 

Fields

Instances

Eq (CPs f) Source # 

Methods

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

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

Ord (CPs f) Source # 

Methods

compare :: CPs f -> CPs f -> Ordering #

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

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

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

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

max :: CPs f -> CPs f -> CPs f #

min :: CPs f -> CPs f -> CPs f #

Show (CPs f) Source # 

Methods

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

show :: CPs f -> String #

showList :: [CPs f] -> ShowS #

(Numbered f, PrettyTerm f) => Pretty (CPs f) Source # 

Methods

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

pPrint :: CPs f -> Doc #

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

Labels (CPs f) Source # 

Methods

labels :: CPs f -> [Label] Source #

data Passive f Source #

Constructors

SingleCP !(CP f) 
ManyCPs !(CPs f) 

Instances

Eq (Passive f) Source # 

Methods

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

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

Ord (Passive f) Source # 

Methods

compare :: Passive f -> Passive f -> Ordering #

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

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

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

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

max :: Passive f -> Passive f -> Passive f #

min :: Passive f -> Passive f -> Passive f #

Show f => Show (Passive f) Source # 

Methods

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

show :: Passive f -> String #

showList :: [Passive f] -> ShowS #

(Numbered f, PrettyTerm f) => Pretty (Passive f) Source # 
Labels (Passive f) Source # 

Methods

labels :: Passive f -> [Label] Source #

data InitialCP f Source #

Constructors

InitialCP 

Fields

ruleOverlaps :: Twee f -> Term f -> [Int] Source #

overlaps :: [Int] -> Term f -> Term f -> [(Subst f, Int)] Source #

criticalPairs1 :: Function f => Twee f -> [Int] -> Rule f -> [Labelled (Rule f)] -> [Labelled (Critical (Equation f))] Source #

queueCP :: Function f => (Passive f -> State (Twee f) ()) -> (Equation f -> Bool) -> Label -> Label -> Critical (Equation f) -> State (Twee f) () Source #

queueCPs :: (Function f, Ord a) => (Passive f -> State (Twee f) ()) -> Label -> Label -> (Label -> a) -> Labelled (Rule f) -> State (Twee f) () Source #

queueCPsSplit :: Function f => (Passive f -> State (Twee f) ()) -> Label -> Label -> Labelled (Rule f) -> State (Twee f) () Source #

toCPs :: Function f => Twee f -> Label -> Label -> Labelled (Rule f) -> [CP f] Source #

toCP :: Function f => Twee f -> Label -> Label -> (Equation f -> Bool) -> Critical (Equation f) -> Maybe (CP f) Source #

weight :: Function f => Twee f -> Equation f -> Int Source #

cancellations :: Function f => Twee f -> (Equation f -> Bool) -> Equation f -> [Equation f] Source #

trace :: Function f => Twee f -> Event f -> a -> a Source #

traceM :: Function f => Event f -> State (Twee f) () Source #

traceIf :: Bool -> Doc -> a -> a Source #

Orphan instances