Copyright | (c) Masahiro Sakai 2011-2014 |
---|---|
License | BSD-style |
Maintainer | masahiro.sakai@gmail.com |
Stability | provisional |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Extensions |
|
ToySolver.Arith.Cooper.Base
Description
Naive implementation of Cooper's algorithm
Reference:
- http://hagi.is.s.u-tokyo.ac.jp/pub/staff/hagiya/kougiroku/ronri/5.txt
- http://www.cs.cmu.edu/~emc/spring06/home1_files/Presburger%20Arithmetic.ppt
See also:
Synopsis
- type ExprZ = Expr Integer
- data Lit
- type QFFormula = BoolExpr Lit
- fromLAAtom :: Atom Rational -> QFFormula
- (.|.) :: Integer -> ExprZ -> QFFormula
- type Model r = VarMap r
- class Eval m e v | m e -> v where
- eval :: m -> e -> v
- project :: Var -> QFFormula -> (QFFormula, Model Integer -> Model Integer)
- projectN :: VarSet -> QFFormula -> (QFFormula, Model Integer -> Model Integer)
- projectCases :: Var -> QFFormula -> [(QFFormula, Model Integer -> Model Integer)]
- projectCasesN :: VarSet -> QFFormula -> [(QFFormula, Model Integer -> Model Integer)]
- solve :: VarSet -> [Atom Rational] -> Maybe (Model Integer)
- solveQFFormula :: VarSet -> QFFormula -> Maybe (Model Integer)
- solveQFLIRAConj :: VarSet -> [Atom Rational] -> VarSet -> Maybe (Model Rational)
Language of presburger arithmetics
Literals of Presburger arithmetic.
Constructors
IsPos ExprZ |
|
Divisible Bool Integer ExprZ |
|
Instances
Show Lit Source # | |
Eq Lit Source # | |
Ord Lit Source # | |
Complement Lit Source # | |
Variables Lit Source # | |
IsEqRel (Expr Integer) QFFormula Source # | |
IsOrdRel (Expr Integer) QFFormula Source # | |
Defined in ToySolver.Arith.Cooper.Base Methods (.<.) :: Expr Integer -> Expr Integer -> QFFormula Source # (.<=.) :: Expr Integer -> Expr Integer -> QFFormula Source # (.>.) :: Expr Integer -> Expr Integer -> QFFormula Source # (.>=.) :: Expr Integer -> Expr Integer -> QFFormula Source # ordRel :: RelOp -> Expr Integer -> Expr Integer -> QFFormula Source # | |
Eval (Model Integer) Lit Bool Source # | |
class Eval m e v | m e -> v where Source #
Evaluataion of something (e.g. expression or formula) under the model.
Projection
project :: Var -> QFFormula -> (QFFormula, Model Integer -> Model Integer) Source #
returns project
x φ(ψ, lift)
such that:
⊢_LIA ∀y1, …, yn. (∃x. φ) ↔ ψ
where{y1, …, yn} = FV(φ) \ {x}
, and- if
M ⊧_LIA ψ
thenlift M ⊧_LIA φ
.
projectN :: VarSet -> QFFormula -> (QFFormula, Model Integer -> Model Integer) Source #
returns projectN
{x1,…,xm} φ(ψ, lift)
such that:
⊢_LIA ∀y1, …, yn. (∃x1, …, xm. φ) ↔ ψ
where{y1, …, yn} = FV(φ) \ {x1,…,xm}
, and- if
M ⊧_LIA ψ
thenlift M ⊧_LIA φ
.
projectCases :: Var -> QFFormula -> [(QFFormula, Model Integer -> Model Integer)] Source #
returns projectCases
x φ[(ψ_1, lift_1), …, (ψ_m, lift_m)]
such that:
⊢_LIA ∀y1, …, yn. (∃x. φ) ↔ (ψ_1 ∨ … ∨ φ_m)
where{y1, …, yn} = FV(φ) \ {x}
, and- if
M ⊧_LIA ψ_i
thenlift_i M ⊧_LIA φ
.
projectCasesN :: VarSet -> QFFormula -> [(QFFormula, Model Integer -> Model Integer)] Source #
returns projectCasesN
{x1,…,xm} φ[(ψ_1, lift_1), …, (ψ_n, lift_n)]
such that:
⊢_LIA ∀y1, …, yp. (∃x. φ) ↔ (ψ_1 ∨ … ∨ φ_n)
where{y1, …, yp} = FV(φ) \ {x1,…,xm}
, and- if
M ⊧_LIA ψ_i
thenlift_i M ⊧_LIA φ
.
Constraint solving
solve :: VarSet -> [Atom Rational] -> Maybe (Model Integer) Source #
returns solve
{x1,…,xn} φJust M
that M ⊧_LIA φ
when
such M
exists, returns Nothing
otherwise.
FV(φ)
must be a subset of {x1,…,xn}
.
solveQFFormula :: VarSet -> QFFormula -> Maybe (Model Integer) Source #
returns solveQFFormula
{x1,…,xn} φJust M
that M ⊧_LIA φ
when
such M
exists, returns Nothing
otherwise.
FV(φ)
must be a subset of {x1,…,xn}
.