toysolver-0.5.0: Assorted decision procedures for SAT, SMT, Max-SAT, PB, MIP, etc

Copyright(c) Masahiro Sakai 2011-2014
LicenseBSD-style
Maintainermasahiro.sakai@gmail.com
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

ToySolver.Data.MIP.Base

Contents

Description

Mixed-Integer Programming Problems with some commmonly used extensions

Synopsis

The MIP Problem type

data Problem c Source #

Problem

Instances

Functor Problem Source # 

Methods

fmap :: (a -> b) -> Problem a -> Problem b #

(<$) :: a -> Problem b -> Problem a #

Eq c => Eq (Problem c) Source # 

Methods

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

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

Ord c => Ord (Problem c) Source # 

Methods

compare :: Problem c -> Problem c -> Ordering #

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

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

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

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

max :: Problem c -> Problem c -> Problem c #

min :: Problem c -> Problem c -> Problem c #

Show c => Show (Problem c) Source # 

Methods

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

show :: Problem c -> String #

showList :: [Problem c] -> ShowS #

Default (Problem c) Source # 

Methods

def :: Problem c #

Variables (Problem c) Source # 

Methods

vars :: Problem c -> Set Var Source #

type Label = Text Source #

label

Variables

type Var = InternedText Source #

variable

toVar :: String -> Var Source #

convert a string into a variable

fromVar :: Var -> String Source #

convert a variable into a string

Variable types

getVarType :: Problem c -> Var -> VarType Source #

looking up bounds for a variable

Variable bounds

type BoundExpr c = Extended c Source #

type for representing lower/upper bound of variables

data Extended r :: * -> * #

Extended r is an extension of r with positive/negative infinity (±∞).

Constructors

NegInf

negative infinity (-∞)

Finite ~r

finite value

PosInf

positive infinity (+∞)

Instances

Functor Extended 

Methods

fmap :: (a -> b) -> Extended a -> Extended b #

(<$) :: a -> Extended b -> Extended a #

Bounded (Extended r) 
Eq r => Eq (Extended r) 

Methods

(==) :: Extended r -> Extended r -> Bool #

(/=) :: Extended r -> Extended r -> Bool #

(Fractional r, Ord r) => Fractional (Extended r)

Note that Extended r is not a field, nor a ring.

Data r => Data (Extended r) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Extended r -> c (Extended r) #

gunfold :: (forall b a. Data b => c (b -> a) -> c a) -> (forall a. a -> c a) -> Constr -> c (Extended r) #

toConstr :: Extended r -> Constr #

dataTypeOf :: Extended r -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Extended r)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Extended r)) #

gmapT :: (forall b. Data b => b -> b) -> Extended r -> Extended r #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Extended r -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Extended r -> r #

gmapQ :: (forall d. Data d => d -> u) -> Extended r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Extended r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Extended r -> m (Extended r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Extended r -> m (Extended r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Extended r -> m (Extended r) #

(Num r, Ord r) => Num (Extended r)

Note that Extended r is not a field, nor a ring.

PosInf + NegInf is left undefined as usual, but we define 0 * PosInf = 0 * NegInf = 0 by following the convention of probability or measure theory.

Ord r => Ord (Extended r) 

Methods

compare :: Extended r -> Extended r -> Ordering #

(<) :: Extended r -> Extended r -> Bool #

(<=) :: Extended r -> Extended r -> Bool #

(>) :: Extended r -> Extended r -> Bool #

(>=) :: Extended r -> Extended r -> Bool #

max :: Extended r -> Extended r -> Extended r #

min :: Extended r -> Extended r -> Extended r #

Read r => Read (Extended r) 
Show r => Show (Extended r) 

Methods

showsPrec :: Int -> Extended r -> ShowS #

show :: Extended r -> String #

showList :: [Extended r] -> ShowS #

NFData r => NFData (Extended r) 

Methods

rnf :: Extended r -> () #

Hashable r => Hashable (Extended r) 

Methods

hashWithSalt :: Int -> Extended r -> Int #

hash :: Extended r -> Int #

type Bounds c = (BoundExpr c, BoundExpr c) Source #

type for representing lower/upper bound of variables

defaultBounds :: Num c => Bounds c Source #

default bounds

defaultLB :: Num c => BoundExpr c Source #

default lower bound (0)

defaultUB :: BoundExpr c Source #

default upper bound (+∞)

getBounds :: Num c => Problem c -> Var -> Bounds c Source #

looking up bounds for a variable

Variable getters

Expressions

newtype Expr c Source #

expressions

Constructors

Expr [Term c] 

Instances

Functor Expr Source # 

Methods

fmap :: (a -> b) -> Expr a -> Expr b #

(<$) :: a -> Expr b -> Expr a #

Eq c => Eq (Expr c) Source # 

Methods

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

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

Num c => Num (Expr c) Source # 

Methods

(+) :: Expr c -> Expr c -> Expr c #

(-) :: Expr c -> Expr c -> Expr c #

(*) :: Expr c -> Expr c -> Expr c #

negate :: Expr c -> Expr c #

abs :: Expr c -> Expr c #

signum :: Expr c -> Expr c #

fromInteger :: Integer -> Expr c #

Ord c => Ord (Expr c) Source # 

Methods

compare :: Expr c -> Expr c -> Ordering #

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

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

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

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

max :: Expr c -> Expr c -> Expr c #

min :: Expr c -> Expr c -> Expr c #

Show c => Show (Expr c) Source # 

Methods

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

show :: Expr c -> String #

showList :: [Expr c] -> ShowS #

Variables (Expr c) Source # 

Methods

vars :: Expr c -> Set Var Source #

varExpr :: Num c => Var -> Expr c Source #

constExpr :: (Eq c, Num c) => c -> Expr c Source #

terms :: Expr c -> [Term c] Source #

data Term c Source #

terms

Constructors

Term c [Var] 

Instances

Functor Term Source # 

Methods

fmap :: (a -> b) -> Term a -> Term b #

(<$) :: a -> Term b -> Term a #

Eq c => Eq (Term c) Source # 

Methods

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

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

Ord c => Ord (Term c) Source # 

Methods

compare :: Term c -> Term c -> Ordering #

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

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

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

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

max :: Term c -> Term c -> Term c #

min :: Term c -> Term c -> Term c #

Show c => Show (Term c) Source # 

Methods

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

show :: Term c -> String #

showList :: [Term c] -> ShowS #

Variables (Term c) Source # 

Methods

vars :: Term c -> Set Var Source #

Objective function

data OptDir :: * #

The OptDir type represents optimization directions.

Constructors

OptMin

minimization

OptMax

maximization

Instances

Bounded OptDir 
Enum OptDir 
Eq OptDir 

Methods

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

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

Data OptDir 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OptDir -> c OptDir #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OptDir #

toConstr :: OptDir -> Constr #

dataTypeOf :: OptDir -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OptDir) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OptDir) #

gmapT :: (forall b. Data b => b -> b) -> OptDir -> OptDir #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OptDir -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OptDir -> r #

gmapQ :: (forall d. Data d => d -> u) -> OptDir -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OptDir -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OptDir -> m OptDir #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OptDir -> m OptDir #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OptDir -> m OptDir #

Ord OptDir 
Read OptDir 
Show OptDir 
Ix OptDir 
Hashable OptDir 

Methods

hashWithSalt :: Int -> OptDir -> Int #

hash :: OptDir -> Int #

Constraints

Linear (or Quadratic or Polynomial) constraints

(.==.) :: Num c => Expr c -> Expr c -> Constraint c infix 4 Source #

(.<=.) :: Num c => Expr c -> Expr c -> Constraint c infix 4 Source #

(.>=.) :: Num c => Expr c -> Expr c -> Constraint c infix 4 Source #

data RelOp Source #

relational operators

Constructors

Le 
Ge 
Eql 

SOS constraints

data SOSType Source #

types of SOS (special ordered sets) constraints

Constructors

S1

Type 1 SOS constraint

S2

Type 2 SOS constraint

Solutions

data Solution r Source #

Constructors

Solution 

Instances

Functor Solution Source # 

Methods

fmap :: (a -> b) -> Solution a -> Solution b #

(<$) :: a -> Solution b -> Solution a #

Eq r => Eq (Solution r) Source # 

Methods

(==) :: Solution r -> Solution r -> Bool #

(/=) :: Solution r -> Solution r -> Bool #

Ord r => Ord (Solution r) Source # 

Methods

compare :: Solution r -> Solution r -> Ordering #

(<) :: Solution r -> Solution r -> Bool #

(<=) :: Solution r -> Solution r -> Bool #

(>) :: Solution r -> Solution r -> Bool #

(>=) :: Solution r -> Solution r -> Bool #

max :: Solution r -> Solution r -> Solution r #

min :: Solution r -> Solution r -> Solution r #

Show r => Show (Solution r) Source # 

Methods

showsPrec :: Int -> Solution r -> ShowS #

show :: Solution r -> String #

showList :: [Solution r] -> ShowS #

Default (Solution r) Source # 

Methods

def :: Solution r #

File I/O options

Utilities

class Variables a where Source #

Minimal complete definition

vars

Methods

vars :: a -> Set Var Source #