Copyright | (c) Masahiro Sakai 2011-2013 |
---|---|
License | BSD-style |
Maintainer | masahiro.sakai@gmail.com |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Naïve implementation of Fourier-Motzkin Variable Elimination
Reference:
- data Constr
- eqR :: Rat -> Rat -> Constr
- type ExprZ = Expr Integer
- fromLAAtom :: Atom Rational -> DNF Constr
- toLAAtom :: Constr -> Atom Rational
- constraintsToDNF :: [Atom Rational] -> DNF Constr
- simplify :: [Constr] -> Maybe [Constr]
- type Bounds = ([Rat], [Rat], [Rat], [Rat])
- evalBounds :: Model Rational -> Bounds -> Interval Rational
- boundsToConstrs :: Bounds -> Maybe [Constr]
- collectBounds :: Var -> [Constr] -> (Bounds, [Constr])
- project :: Var -> [Atom Rational] -> [([Atom Rational], Model Rational -> Model Rational)]
- project' :: Var -> [Constr] -> Maybe ([Constr], Model Rational -> Model Rational)
- projectN :: VarSet -> [Atom Rational] -> [([Atom Rational], Model Rational -> Model Rational)]
- projectN' :: VarSet -> [Constr] -> Maybe ([Constr], Model Rational -> Model Rational)
- solve :: VarSet -> [Atom Rational] -> Maybe (Model Rational)
- solve' :: VarSet -> [Constr] -> Maybe (Model Rational)
- type Rat = (ExprZ, Integer)
- toRat :: Expr Rational -> Rat
Primitive constraints
Atomic constraint
Bounds
boundsToConstrs :: Bounds -> Maybe [Constr] Source
Projection
project :: Var -> [Atom Rational] -> [([Atom Rational], Model Rational -> Model Rational)] Source
returns project
x φ[(ψ_1, lift_1), …, (ψ_m, lift_m)]
such that:
⊢_LRA ∀y1, …, yn. (∃x. φ) ↔ (ψ_1 ∨ … ∨ φ_m)
where{y1, …, yn} = FV(φ) \ {x}
, and- if
M ⊧_LRA ψ_i
thenlift_i M ⊧_LRA φ
.
projectN :: VarSet -> [Atom Rational] -> [([Atom Rational], Model Rational -> Model Rational)] Source
returns projectN
{x1,…,xm} φ[(ψ_1, lift_1), …, (ψ_n, lift_n)]
such that:
⊢_LRA ∀y1, …, yp. (∃x. φ) ↔ (ψ_1 ∨ … ∨ φ_n)
where{y1, …, yp} = FV(φ) \ {x1,…,xm}
, and- if
M ⊧_LRA ψ_i
thenlift_i M ⊧_LRA φ
.
Solving
solve :: VarSet -> [Atom Rational] -> Maybe (Model Rational) Source
returns solve
{x1,…,xn} φJust M
that M ⊧_LRA φ
when
such M
exists, returns Nothing
otherwise.
FV(φ)
must be a subset of {x1,…,xn}
.