ghc-typelits-presburger-0.3.0.0: Presburger Arithmetic Solver for GHC Type-level natural numbers.

Safe HaskellNone
LanguageHaskell2010

GHC.TypeLits.Presburger.Types

Description

Since 0.3.0.0

Synopsis

Documentation

data Expr Source #

The type of integer expressions. Variable names must be non-negative.

Constructors

Expr :+ Expr infixl 6

Addition

Expr :- Expr infixl 6

Subtraction

Integer :* Expr infixl 7

Multiplication by a constant

Negate Expr

Negation

Var Name

Variable

K Integer

Constant

If Prop Expr Expr

A conditional expression

Div Expr Integer

Division, rounds down

Mod Expr Integer

Non-negative remainder

Instances
Eq Expr Source # 
Instance details

Defined in Data.Integer.SAT

Methods

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

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

Ord Expr Source # 
Instance details

Defined in Data.Integer.SAT

Methods

compare :: Expr -> Expr -> Ordering #

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

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

(>) :: Expr -> Expr -> Bool #

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

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

Read Expr Source # 
Instance details

Defined in Data.Integer.SAT

Show Expr Source # 
Instance details

Defined in Data.Integer.SAT

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

data Prop Source #

The type of proposition.

Constructors

PTrue 
PFalse 
Prop :|| Prop infixr 2 
Prop :&& Prop infixr 3 
Not Prop 
Expr :== Expr infix 4 
Expr :/= Expr infix 4 
Expr :< Expr infix 4 
Expr :> Expr infix 4 
Expr :<= Expr infix 4 
Expr :>= Expr infix 4 
Instances
Eq Prop Source # 
Instance details

Defined in Data.Integer.SAT

Methods

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

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

Ord Prop Source # 
Instance details

Defined in Data.Integer.SAT

Methods

compare :: Prop -> Prop -> Ordering #

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

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

(>) :: Prop -> Prop -> Bool #

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

max :: Prop -> Prop -> Prop #

min :: Prop -> Prop -> Prop #

Read Prop Source # 
Instance details

Defined in Data.Integer.SAT

Show Prop Source # 
Instance details

Defined in Data.Integer.SAT

Methods

showsPrec :: Int -> Prop -> ShowS #

show :: Prop -> String #

showList :: [Prop] -> ShowS #

data PropSet Source #

A collection of propositions.

Instances
Show PropSet Source # 
Instance details

Defined in Data.Integer.SAT

noProps :: PropSet Source #

An empty collection of propositions.

assert :: Prop -> PropSet -> PropSet Source #

Add a new proposition to an existing collection.

checkSat :: PropSet -> Maybe [(Int, Integer)] Source #

Extract a model from a consistent set of propositions. Returns Nothing if the assertions have no model. If a variable does not appear in the assignment, then it is 0 (?).

toName :: Int -> Name Source #