math-programming-0.5.1: A library for formulating and solving math programs.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.Programming

Description

A library for modeling and solving linear and integer programs.

This library is merely a frontend to various solver backends. At the time this was written, the only known supported backend is GLPK.

This page includes a high-level overview of the model building DSL, as well as a deeper dive into the core monadic interface.

Synopsis

Model-building DSL

We provide a monadic DSL for specifying math programs. This DSL builds up programs statefully, rather than building some pure, abstract representation of a math program.

Creating variables

Continuous variables

free :: MonadLP v c o m => m v Source #

Create a new free variable.

bounded :: MonadLP v c o m => Double -> Double -> m v Source #

Create a new variable bounded between two values.

nonNeg :: MonadLP v c o m => m v Source #

Create a new non-negative variable.

nonPos :: MonadLP v c o m => m v Source #

Create a new non-positive variable.

Discrete variables

integer :: MonadIP v c o m => m v Source #

Create an integer-valued variable.

binary :: MonadIP v c o m => m v Source #

Create a binary variable.

nonNegInteger :: MonadIP v c o m => m v Source #

Create an integer-value variable that takes on non-negative values.

nonPosInteger :: MonadIP v c o m => m v Source #

Create an integer-value variable that takes on non-positive values.

Modifying variables

Regardless of the helper functions used above to create a variable, you can modify its behavior using the following modifiers.

within :: MonadLP v c o m => m v -> Bounds -> m v Source #

Constrain a variable to take on certain values.

This function is designed to be used as an infix operator, e.g.

integer `within` 'Interval 3 7'

creates an integer variable that can take on values 3, 4, 5, 6, or 7.

asKind :: MonadIP v c o m => m v -> Domain -> m v Source #

Set the type of a variable.

This function is designed to be used as an infix operator, e.g.

free `asKind` Binary

Creating constraints

An Inequality a is an inequality over the type a, which in turn is typically an Expr v for some variable type v. Despite the name, Inequality can also represent equality constraints directly.

As an alternative to constructing an inequality and passing it to addConstraint, we can use the convenience operators below. Since linear programming constraints often involve constant bounds, we offer operators specialized for both expressions and constants. The mnemonic is that . characters point to expressions

Equality constraints

(.==.) :: MonadLP v c o m => Expr v -> Expr v -> m c infix 4 Source #

An equality constraint

(==.) :: MonadLP v c o m => Double -> Expr v -> m c infix 4 Source #

An equality constraint with a numeric left-hand side

(.==) :: MonadLP v c o m => Expr v -> Double -> m c infix 4 Source #

An equality constraint with a numeric right-hand side

Less-than constraints

(.<=.) :: MonadLP v c o m => Expr v -> Expr v -> m c infix 4 Source #

A less-than or equal-to constraint

(<=.) :: MonadLP v c o m => Double -> Expr v -> m c infix 4 Source #

A less-than or equal-to constraint with a numeric left-hand side

(.<=) :: MonadLP v c o m => Expr v -> Double -> m c infix 4 Source #

A less-than or equal-to constraint with a numeric right-hand side

Greater-than constraints

(.>=.) :: MonadLP v c o m => Expr v -> Expr v -> m c infix 4 Source #

A greater-than or equal-to constraint

(>=.) :: MonadLP v c o m => Double -> Expr v -> m c infix 4 Source #

A greater-than or equal-to constraint with a numeric left-hand side

(.>=) :: MonadLP v c o m => Expr v -> Double -> m c infix 4 Source #

A greater-than or equal-to constraint with a numeric right-hand side

Creating objectives

minimize :: MonadLP v c o m => Expr v -> m o Source #

Create an objective to be minimized.

maximize :: MonadLP v c o m => Expr v -> m o Source #

Create an objective to be maximized.

Creating linear expressions

A LinExpr a b is a linear expression over variables of type b with coefficients of type a (typically Double.) We provide a number of operators to build up linear expressions naturally. The mnemonic is that . characters point to expressions.

var :: Num a => b -> LinExpr a b Source #

A linear expression with a single variable term.

con :: a -> LinExpr a b Source #

A linear expression with only a constant term.

(.*) :: Num a => b -> a -> LinExpr a b infixl 7 Source #

Construct a term in a linear expression by multiplying a variable by a constant.

(*.) :: Num a => a -> b -> LinExpr a b infixl 7 Source #

Construct a term in a linear expression by multiplying a constant by a variable.

(.+.) :: Num a => LinExpr a b -> LinExpr a b -> LinExpr a b infixl 6 Source #

Addition of linear expressions.

(.-.) :: Num a => LinExpr a b -> LinExpr a b -> LinExpr a b infixl 6 Source #

The difference of linear expressions.

(./) :: Fractional a => b -> a -> LinExpr a b infixl 7 Source #

Construct a term in a linear expression by dividing a variable by a constant.

eval :: Num a => LinExpr a a -> a Source #

Reduce an expression to its value.

simplify :: (Num a, Ord b) => LinExpr a b -> LinExpr a b Source #

Simplify an expression by grouping like terms.

vsum :: Num a => [b] -> LinExpr a b Source #

The sum of variable terms with coefficients of unity.

esum :: Num a => Foldable t => t (LinExpr a b) -> LinExpr a b Source #

The sum of linear expressions.

scale :: Num a => a -> LinExpr a b -> LinExpr a b Source #

Multiplication of linear expressions by a constant.

Math programs

The MonadLP and MonadIP classes provide low-level APIs for defining linear and integer programs, respectively, although the high-level DSL will typically be easier to work with.

Linear programs

class Monad m => MonadLP v c o m | m -> v c o where Source #

A linear program.

This is a monadic context for formulating and solving linear programs. The types v, c, and o refer to the types of variables, constraints, and objectives, respectively, used by a particular solver backend.

Methods

addVariable :: m v Source #

Add a new (free) variable to the model.

See free, bounded, nonNeg, and nonPos as higher-level alternatives.

deleteVariable :: v -> m () Source #

Remove a variable from the model.

getVariableName :: v -> m Text Source #

Get the name of a variable.

setVariableName :: v -> Text -> m () Source #

Set a name for a variable.

getVariableBounds :: v -> m Bounds Source #

Retrieve the current bounds associated with a variable.

setVariableBounds :: v -> Bounds -> m () Source #

Apply bounds to a variable.

See within as a higher-level alternative.

getVariableValue :: v -> m Double Source #

Get the value of a variable in the current solution.

This value could be arbitrary if no solve has been completed, or a solve produced an infeasible or unbounded solution.

addConstraint :: Inequality (Expr v) -> m c Source #

Add a constraint representing the given inequality to the model.

See the .==., .==#, ==., .>=., .>=, >=., .<=., .<=, and <=. functions as higher-level alternatives.

deleteConstraint :: c -> m () Source #

Remove a constraint from the model.

getConstraintName :: c -> m Text Source #

Get the name of a constraint.

setConstraintName :: c -> Text -> m () Source #

Set a name for a constraint.

getConstraintValue :: c -> m Double Source #

Get the dual value associated with a constraint.

addObjective :: Expr v -> m o Source #

Add an objective to the problem.

Depending on the solver backend, this might replace an existing objective.

deleteObjective :: o -> m () Source #

Remove an objective from the model.

getObjectiveName :: o -> m Text Source #

Get the name of a objective.

setObjectiveName :: o -> Text -> m () Source #

Set a name for a objective.

getObjectiveSense :: o -> m Sense Source #

Get the sense of an objective.

setObjectiveSense :: o -> Sense -> m () Source #

Set the sense of an objective.

getObjectiveValue :: o -> m Double Source #

Get the value of an objective.

getTimeout :: m Double Source #

Get the timeout associated with a problem.

setTimeout :: Double -> m () Source #

Set the timeout associated with a problem.

optimizeLP :: m SolutionStatus Source #

Compute an LP-optimal solution.

Instances

Instances details
MonadLP v c o m => MonadLP v c o (ReaderT r m) Source # 
Instance details

Defined in Math.Programming.Types

MonadLP v c o m => MonadLP v c o (StateT s m) Source # 
Instance details

Defined in Math.Programming.Types

(MonadLP v c o m, Monoid w) => MonadLP v c o (WriterT w m) Source # 
Instance details

Defined in Math.Programming.Types

(MonadLP v c o m, Monoid w) => MonadLP v c o (RWST r w s m) Source # 
Instance details

Defined in Math.Programming.Types

Methods

addVariable :: RWST r w s m v Source #

deleteVariable :: v -> RWST r w s m () Source #

getVariableName :: v -> RWST r w s m Text Source #

setVariableName :: v -> Text -> RWST r w s m () Source #

getVariableBounds :: v -> RWST r w s m Bounds Source #

setVariableBounds :: v -> Bounds -> RWST r w s m () Source #

getVariableValue :: v -> RWST r w s m Double Source #

addConstraint :: Inequality (Expr v) -> RWST r w s m c Source #

deleteConstraint :: c -> RWST r w s m () Source #

getConstraintName :: c -> RWST r w s m Text Source #

setConstraintName :: c -> Text -> RWST r w s m () Source #

getConstraintValue :: c -> RWST r w s m Double Source #

addObjective :: Expr v -> RWST r w s m o Source #

deleteObjective :: o -> RWST r w s m () Source #

getObjectiveName :: o -> RWST r w s m Text Source #

setObjectiveName :: o -> Text -> RWST r w s m () Source #

getObjectiveSense :: o -> RWST r w s m Sense Source #

setObjectiveSense :: o -> Sense -> RWST r w s m () Source #

getObjectiveValue :: o -> RWST r w s m Double Source #

getTimeout :: RWST r w s m Double Source #

setTimeout :: Double -> RWST r w s m () Source #

optimizeLP :: RWST r w s m SolutionStatus Source #

Integer programs

class MonadLP v c o m => MonadIP v c o m | m -> v c o where Source #

A (mixed) integer program.

In addition to the methods of the MonadLP class, this monad supports constraining variables to be either continuous or discrete.

data Domain Source #

The type of values that a variable can take on.

Note that the Integer constructor does not interfere with the Integer type, as the Integer type does not define a constuctor of the same name. The ambiguity is unfortunate, but other natural nomenclature such as Integral are similarly conflicted.

Constructors

Continuous

The variable lies in the real numbers

Integer

The variable lies in the integers

Binary

The variable lies in the set {0, 1}.

Instances

Instances details
Read Domain Source # 
Instance details

Defined in Math.Programming.Types

Show Domain Source # 
Instance details

Defined in Math.Programming.Types

Other types and functions

evalExpr :: MonadLP v c o m => Expr v -> m Double Source #

Get the value of a linear expression in the current solution.

formatExpr :: MonadLP v c o m => Expr v -> m Text Source #

type Expr = LinExpr Double Source #

A convient shorthand for the type of linear expressions used in models.

data Bounds Source #

An interval of the real numbers.

Constructors

NonNegativeReals

The non-negative reals.

NonPositiveReals

The non-positive reals.

Interval Double Double

Any closed interval of the reals.

Free

Any real number.

Instances

Instances details
Read Bounds Source # 
Instance details

Defined in Math.Programming.Types

Show Bounds Source # 
Instance details

Defined in Math.Programming.Types

data SolutionStatus Source #

The outcome of an optimization.

Constructors

Optimal

An optimal solution has been found.

Feasible

A feasible solution has been found. The result may or may not be optimal.

Infeasible

The model has been proven to be infeasible.

Unbounded

The model has been proven to be unbounded.

Error

An error was encountered during the solve. Instance-specific methods should be used to determine what occurred.

data Sense Source #

Whether a math program is minimizing or maximizing its objective.

Constructors

Minimization 
Maximization 

Instances

Instances details
Read Sense Source # 
Instance details

Defined in Math.Programming.Types

Show Sense Source # 
Instance details

Defined in Math.Programming.Types

Methods

showsPrec :: Int -> Sense -> ShowS #

show :: Sense -> String #

showList :: [Sense] -> ShowS #

Eq Sense Source # 
Instance details

Defined in Math.Programming.Types

Methods

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

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

Ord Sense Source # 
Instance details

Defined in Math.Programming.Types

Methods

compare :: Sense -> Sense -> Ordering #

(<) :: Sense -> Sense -> Bool #

(<=) :: Sense -> Sense -> Bool #

(>) :: Sense -> Sense -> Bool #

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

max :: Sense -> Sense -> Sense #

min :: Sense -> Sense -> Sense #

data Inequality a Source #

Non-strict inequalities.

Constructors

Inequality Ordering a a 

Instances

Instances details
Foldable Inequality Source # 
Instance details

Defined in Math.Programming.Types

Methods

fold :: Monoid m => Inequality m -> m #

foldMap :: Monoid m => (a -> m) -> Inequality a -> m #

foldMap' :: Monoid m => (a -> m) -> Inequality a -> m #

foldr :: (a -> b -> b) -> b -> Inequality a -> b #

foldr' :: (a -> b -> b) -> b -> Inequality a -> b #

foldl :: (b -> a -> b) -> b -> Inequality a -> b #

foldl' :: (b -> a -> b) -> b -> Inequality a -> b #

foldr1 :: (a -> a -> a) -> Inequality a -> a #

foldl1 :: (a -> a -> a) -> Inequality a -> a #

toList :: Inequality a -> [a] #

null :: Inequality a -> Bool #

length :: Inequality a -> Int #

elem :: Eq a => a -> Inequality a -> Bool #

maximum :: Ord a => Inequality a -> a #

minimum :: Ord a => Inequality a -> a #

sum :: Num a => Inequality a -> a #

product :: Num a => Inequality a -> a #

Traversable Inequality Source # 
Instance details

Defined in Math.Programming.Types

Methods

traverse :: Applicative f => (a -> f b) -> Inequality a -> f (Inequality b) #

sequenceA :: Applicative f => Inequality (f a) -> f (Inequality a) #

mapM :: Monad m => (a -> m b) -> Inequality a -> m (Inequality b) #

sequence :: Monad m => Inequality (m a) -> m (Inequality a) #

Functor Inequality Source # 
Instance details

Defined in Math.Programming.Types

Methods

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

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

Read a => Read (Inequality a) Source # 
Instance details

Defined in Math.Programming.Types

Show a => Show (Inequality a) Source # 
Instance details

Defined in Math.Programming.Types

data LinExpr a b Source #

A linear expression.

Linear expressions contain symbolic variables of type b and numeric coefficients of type a. Often a will be Double, and b will be whatever variable type your linear program uses.

Constructors

LinExpr ![(a, b)] !a 

Instances

Instances details
Foldable (LinExpr a) Source # 
Instance details

Defined in Math.Programming.LinExpr

Methods

fold :: Monoid m => LinExpr a m -> m #

foldMap :: Monoid m => (a0 -> m) -> LinExpr a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> LinExpr a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> LinExpr a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> LinExpr a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> LinExpr a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> LinExpr a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> LinExpr a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> LinExpr a a0 -> a0 #

toList :: LinExpr a a0 -> [a0] #

null :: LinExpr a a0 -> Bool #

length :: LinExpr a a0 -> Int #

elem :: Eq a0 => a0 -> LinExpr a a0 -> Bool #

maximum :: Ord a0 => LinExpr a a0 -> a0 #

minimum :: Ord a0 => LinExpr a a0 -> a0 #

sum :: Num a0 => LinExpr a a0 -> a0 #

product :: Num a0 => LinExpr a a0 -> a0 #

Traversable (LinExpr a) Source # 
Instance details

Defined in Math.Programming.LinExpr

Methods

traverse :: Applicative f => (a0 -> f b) -> LinExpr a a0 -> f (LinExpr a b) #

sequenceA :: Applicative f => LinExpr a (f a0) -> f (LinExpr a a0) #

mapM :: Monad m => (a0 -> m b) -> LinExpr a a0 -> m (LinExpr a b) #

sequence :: Monad m => LinExpr a (m a0) -> m (LinExpr a a0) #

Functor (LinExpr a) Source # 
Instance details

Defined in Math.Programming.LinExpr

Methods

fmap :: (a0 -> b) -> LinExpr a a0 -> LinExpr a b #

(<$) :: a0 -> LinExpr a b -> LinExpr a a0 #

Num a => Monoid (LinExpr a b) Source # 
Instance details

Defined in Math.Programming.LinExpr

Methods

mempty :: LinExpr a b #

mappend :: LinExpr a b -> LinExpr a b -> LinExpr a b #

mconcat :: [LinExpr a b] -> LinExpr a b #

Num a => Semigroup (LinExpr a b) Source # 
Instance details

Defined in Math.Programming.LinExpr

Methods

(<>) :: LinExpr a b -> LinExpr a b -> LinExpr a b #

sconcat :: NonEmpty (LinExpr a b) -> LinExpr a b #

stimes :: Integral b0 => b0 -> LinExpr a b -> LinExpr a b #

(Read a, Read b) => Read (LinExpr a b) Source # 
Instance details

Defined in Math.Programming.LinExpr

(Show a, Show b) => Show (LinExpr a b) Source # 
Instance details

Defined in Math.Programming.LinExpr

Methods

showsPrec :: Int -> LinExpr a b -> ShowS #

show :: LinExpr a b -> String #

showList :: [LinExpr a b] -> ShowS #

(Eq a, Eq b) => Eq (LinExpr a b) Source # 
Instance details

Defined in Math.Programming.LinExpr

Methods

(==) :: LinExpr a b -> LinExpr a b -> Bool #

(/=) :: LinExpr a b -> LinExpr a b -> Bool #

Naming model attributes

withVariableName :: MonadLP v c o m => m v -> Text -> m v Source #

withConstraintName :: MonadLP v c o m => m c -> Text -> m c Source #

withObjectiveName :: MonadLP v c o m => m o -> Text -> m o Source #