twee-lib-2.1.1: An equational theorem prover

Safe HaskellNone
LanguageHaskell2010

Twee.Constraints

Description

Solving constraints on variable ordering.

Synopsis

Documentation

data Atom f Source #

Constructors

Constant (Fun f) 
Variable Var 

Instances

Eq (Atom f) Source # 

Methods

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

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

Ord (Atom f) Source # 

Methods

compare :: Atom f -> Atom f -> Ordering #

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

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

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

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

max :: Atom f -> Atom f -> Atom f #

min :: Atom f -> Atom f -> Atom f #

Show (Atom f) Source # 

Methods

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

show :: Atom f -> String #

showList :: [Atom f] -> ShowS #

PrettyTerm f => Pretty (Atom f) Source # 

Methods

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

pPrint :: Atom f -> Doc #

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

atoms :: Term f -> [Atom f] Source #

toTerm :: Atom f -> Term f Source #

data Formula f Source #

Constructors

Less (Atom f) (Atom f) 
LessEq (Atom f) (Atom f) 
And [Formula f] 
Or [Formula f] 

Instances

Eq (Formula f) Source # 

Methods

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

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

Ord (Formula f) Source # 

Methods

compare :: Formula f -> Formula f -> Ordering #

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

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

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

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

max :: Formula f -> Formula f -> Formula f #

min :: Formula f -> Formula f -> Formula f #

Show (Formula f) Source # 

Methods

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

show :: Formula f -> String #

showList :: [Formula f] -> ShowS #

PrettyTerm f => Pretty (Formula f) Source # 

conj :: Foldable t => t (Formula f) -> Formula f Source #

disj :: Foldable t => t (Formula f) -> Formula f Source #

data Branch f Source #

Constructors

Branch 

Fields

Instances

Eq (Branch f) Source # 

Methods

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

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

Ord (Branch f) Source # 

Methods

compare :: Branch f -> Branch f -> Ordering #

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

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

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

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

max :: Branch f -> Branch f -> Branch f #

min :: Branch f -> Branch f -> Branch f #

PrettyTerm f => Pretty (Branch f) Source # 

norm :: Eq f => Branch f -> Atom f -> Atom f Source #

formAnd :: (Minimal f, Ordered f) => Formula f -> [Branch f] -> [Branch f] Source #

branches :: (Minimal f, Ordered f) => Formula f -> [Branch f] Source #

addLess :: (Minimal f, Ordered f) => Atom f -> Atom f -> Branch f -> [Branch f] Source #

addEquals :: (Minimal f, Ordered f) => Atom f -> Atom f -> Branch f -> [Branch f] Source #

addTerm :: (Minimal f, Ordered f) => Atom f -> Branch f -> Branch f Source #

newtype Model f Source #

Constructors

Model (Map (Atom f) (Int, Int)) 

Instances

Eq (Model f) Source # 

Methods

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

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

Show (Model f) Source # 

Methods

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

show :: Model f -> String #

showList :: [Model f] -> ShowS #

PrettyTerm f => Pretty (Model f) Source # 

modelFromOrder :: (Minimal f, Ord f) => [Atom f] -> Model f Source #

varInModel :: (Minimal f, Ord f) => Model f -> Var -> Bool Source #

varGroups :: (Minimal f, Ord f) => Model f -> [(Fun f, [Var], Maybe (Fun f))] Source #

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 #

solve :: (Minimal f, Ordered f, PrettyTerm f) => [Atom f] -> Branch f -> Either (Model f) (Subst f) 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.

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.

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.