| Copyright | (c) Masahiro Sakai 2011-2014 |
|---|---|
| License | BSD-style |
| Maintainer | masahiro.sakai@gmail.com |
| Stability | provisional |
| Portability | non-portable (MultiParamTypeClasses, FlexibleInstances) |
| Safe Haskell | None |
| Language | Haskell2010 |
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:
- type ExprZ = Expr Integer
- data Lit
- evalLit :: Model Integer -> Lit -> Bool
- type QFFormula = BoolExpr Lit
- fromLAAtom :: Atom Rational -> QFFormula
- (.|.) :: Integer -> ExprZ -> QFFormula
- evalQFFormula :: Model Integer -> QFFormula -> Bool
- type Model r = VarMap r
- 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.
fromLAAtom :: Atom Rational -> QFFormula Source
evalQFFormula :: Model Integer -> QFFormula -> Bool Source
returns whether evalQFFormula M φM ⊧_LIA φ or not.
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 ψ_ithenlift_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 ψ_ithenlift_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}.
solveQFLIRAConj :: VarSet -> [Atom Rational] -> VarSet -> Maybe (Model Rational) Source
returns solveQFLIRAConj {x1,…,xn} φ IJust M that M ⊧_LIRA φ when
such M exists, returns Nothing otherwise.
FV(φ)must be a subset of{x1,…,xn}.Iis a set of integer variables and must be a subset of{x1,…,xn}.