toysolver-0.8.1: Assorted decision procedures for SAT, SMT, Max-SAT, PB, MIP, etc
Copyright(c) Masahiro Sakai 2012
LicenseBSD-style
Maintainermasahiro.sakai@gmail.com
Stabilityprovisional
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • BangPatterns
  • ExplicitForAll

ToySolver.Arith.CAD

Description

Synopsis

Basic data structures

data Point c Source #

Constructors

NegInf 
RootOf (UPolynomial c) Int 
PosInf 

Instances

Instances details
Show c => Show (Point c) Source # 
Instance details

Defined in ToySolver.Arith.CAD

Methods

showsPrec :: Int -> Point c -> ShowS #

show :: Point c -> String #

showList :: [Point c] -> ShowS #

Eq c => Eq (Point c) Source # 
Instance details

Defined in ToySolver.Arith.CAD

Methods

(==) :: Point c -> Point c -> Bool #

(/=) :: Point c -> Point c -> Bool #

Ord c => Ord (Point c) Source # 
Instance details

Defined in ToySolver.Arith.CAD

Methods

compare :: Point c -> Point c -> Ordering #

(<) :: Point c -> Point c -> Bool #

(<=) :: Point c -> Point c -> Bool #

(>) :: Point c -> Point c -> Bool #

(>=) :: Point c -> Point c -> Bool #

max :: Point c -> Point c -> Point c #

min :: Point c -> Point c -> Point c #

data Cell c Source #

Constructors

Point (Point c) 
Interval (Point c) (Point c) 

Instances

Instances details
Show c => Show (Cell c) Source # 
Instance details

Defined in ToySolver.Arith.CAD

Methods

showsPrec :: Int -> Cell c -> ShowS #

show :: Cell c -> String #

showList :: [Cell c] -> ShowS #

Eq c => Eq (Cell c) Source # 
Instance details

Defined in ToySolver.Arith.CAD

Methods

(==) :: Cell c -> Cell c -> Bool #

(/=) :: Cell c -> Cell c -> Bool #

Ord c => Ord (Cell c) Source # 
Instance details

Defined in ToySolver.Arith.CAD

Methods

compare :: Cell c -> Cell c -> Ordering #

(<) :: Cell c -> Cell c -> Bool #

(<=) :: Cell c -> Cell c -> Bool #

(>) :: Cell c -> Cell c -> Bool #

(>=) :: Cell c -> Cell c -> Bool #

max :: Cell c -> Cell c -> Cell c #

min :: Cell c -> Cell c -> Cell c #

Projection

project :: (Ord v, Show v, PrettyVar v) => v -> [OrdRel (Polynomial Rational v)] -> [([OrdRel (Polynomial Rational v)], Model v -> Model v)] Source #

project' :: forall v. (Ord v, Show v, PrettyVar v) => [(UPolynomial (Polynomial Rational v), [Sign])] -> [([(Polynomial Rational v, [Sign])], [Cell (Polynomial Rational v)])] Source #

projectN :: (Ord v, Show v, PrettyVar v) => Set v -> [OrdRel (Polynomial Rational v)] -> [([OrdRel (Polynomial Rational v)], Model v -> Model v)] Source #

projectN' :: (Ord v, Show v, PrettyVar v) => Set v -> [(Polynomial Rational v, [Sign])] -> [([(Polynomial Rational v, [Sign])], Model v -> Model v)] Source #

Solving

solve :: forall v. (Ord v, Show v, PrettyVar v) => Set v -> [OrdRel (Polynomial Rational v)] -> Maybe (Model v) Source #

solve' :: forall v. (Ord v, Show v, PrettyVar v) => Set v -> [(Polynomial Rational v, [Sign])] -> Maybe (Model v) Source #

Model

type Model v = Map v AReal Source #