math-programming-0.3.0: A library for formulating and solving math programs.

Safe HaskellSafe
LanguageHaskell2010

Math.Programming.Types

Synopsis

Documentation

type Expr m = LinearExpression (Numeric m) (Variable m) Source #

A convient shorthand for the type of linear expressions used in a given model.

class (Monad m, Num (Numeric m)) => LPMonad m where Source #

A monad for formulating and solving linear programs.

We manipulate linear programs and their settings using the Mutable typeclass.

Associated Types

type Numeric m :: * Source #

The numeric type used in the model.

data Variable m :: * Source #

The type of variables in the model. LPMonad treats these as opaque values, but instances may expose more details.

data Constraint m :: * Source #

The type of constraints in the model. LPMonad treats these as opaque values, but instances may expose more details.

data Objective m :: * Source #

The type of objectives in the model. LPMonad treats these as opaque values, but instances may expose more details.

Methods

addVariable :: m (Variable m) Source #

Create a new decision variable in the model.

This variable will be initialized to be a non-negative continuous variable.

removeVariable :: Variable m -> m () Source #

Remove a decision variable from the model.

The variable cannot be used after being deleted.

getVariableName :: Variable m -> m String Source #

Get the name of the variable.

setVariableName :: Variable m -> String -> m () Source #

Set the name of the variable.

getVariableBounds :: Variable m -> m (Bounds (Numeric m)) Source #

Get the allowed values of a variable.

setVariableBounds :: Variable m -> Bounds (Numeric m) -> m () Source #

Constrain a variable to take on certain values.

getVariableValue :: Variable m -> m (Numeric m) Source #

Get the value of a variable in the current solution.

addConstraint :: Inequality (LinearExpression (Numeric m) (Variable m)) -> m (Constraint m) Source #

Add a constraint to the model represented by an inequality.

removeConstraint :: Constraint m -> m () Source #

Remove a constraint from the model.

The constraint cannot used after being deleted.

getConstraintName :: Constraint m -> m String Source #

Get the name of the constraint.

setConstraintName :: Constraint m -> String -> m () Source #

Set the name of the constraint.

getDualValue :: Constraint m -> m (Numeric m) Source #

Get the value of the dual variable associated with the constraint in the current solution.

This value has no meaning if the current solution is not an LP solution.

addObjective :: LinearExpression (Numeric m) (Variable m) -> m (Objective m) Source #

Add a constraint to the model represented by an inequality.

getObjectiveName :: Objective m -> m String Source #

Get the name of the objective.

setObjectiveName :: Objective m -> String -> m () Source #

Set the name of the objective.

getObjectiveSense :: Objective m -> m Sense Source #

Whether the objective is to be minimized or maximized.

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

Set whether the objective is to be minimized or maximized.

getObjectiveValue :: Objective m -> m (Numeric m) Source #

Get the value of the objective in the current solution.

getTimeout :: m Double Source #

Get the number of seconds the solver is allowed to run before halting.

setTimeout :: Double -> m () Source #

Set the number of seconds the solver is allowed to run before halting.

optimizeLP :: m SolutionStatus Source #

Optimize the continuous relaxation of the model.

writeFormulation :: FilePath -> m () Source #

Write out the formulation.

class LPMonad m => IPMonad m where Source #

A (mixed) integer program.

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

Methods

optimizeIP :: m SolutionStatus Source #

Optimize the mixed-integer program.

getVariableDomain :: Variable m -> m Domain Source #

Get the domain of a variable.

setVariableDomain :: Variable m -> Domain -> m () Source #

Set the domain of a variable.

getRelativeMIPGap :: m Double Source #

Get the allowed relative gap between LP and IP solutions.

setRelativeMIPGap :: Double -> m () Source #

Set the allowed relative gap between LP and IP solutions.

data Sense Source #

Whether a math program is minimizing or maximizing its objective.

Constructors

Minimization 
Maximization 
Instances
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 #

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 #

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 Bounds b Source #

An interval of the real numbers.

Constructors

NonNegativeReals

The non-negative reals.

NonPositiveReals

The non-positive reals.

Interval b b

Any closed interval of the reals.

Free

Any real number.

Instances
Read b => Read (Bounds b) Source # 
Instance details

Defined in Math.Programming.Types

Show b => Show (Bounds b) Source # 
Instance details

Defined in Math.Programming.Types

Methods

showsPrec :: Int -> Bounds b -> ShowS #

show :: Bounds b -> String #

showList :: [Bounds b] -> ShowS #

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
Read Domain Source # 
Instance details

Defined in Math.Programming.Types

Show Domain Source # 
Instance details

Defined in Math.Programming.Types

class Nameable m a where Source #

Methods

getName :: a -> m String Source #

setName :: a -> String -> m () Source #

Instances
LPMonad m => Nameable m (Objective m) Source # 
Instance details

Defined in Math.Programming.Types

Methods

getName :: Objective m -> m String Source #

setName :: Objective m -> String -> m () Source #

LPMonad m => Nameable m (Constraint m) Source # 
Instance details

Defined in Math.Programming.Types

Methods

getName :: Constraint m -> m String Source #

setName :: Constraint m -> String -> m () Source #

LPMonad m => Nameable m (Variable m) Source # 
Instance details

Defined in Math.Programming.Types

Methods

getName :: Variable m -> m String Source #

setName :: Variable m -> String -> m () Source #

data LinearExpression a b Source #

A linear expression containing symbolic variables of type b and numeric coefficients of type a.

Using Strings to denote variables and Doubles as our numeric type, we could express 3 x + 2 y + 1 as

  LinearExpression [(3, "x"), (2, "y")] 1

Constructors

LinearExpression [(a, b)] a 
Instances
Bifunctor LinearExpression Source # 
Instance details

Defined in Math.Programming.Types

Methods

bimap :: (a -> b) -> (c -> d) -> LinearExpression a c -> LinearExpression b d #

first :: (a -> b) -> LinearExpression a c -> LinearExpression b c #

second :: (b -> c) -> LinearExpression a b -> LinearExpression a c #

Functor (LinearExpression a) Source # 
Instance details

Defined in Math.Programming.Types

Methods

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

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

Foldable (LinearExpression a) Source # 
Instance details

Defined in Math.Programming.Types

Methods

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

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

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

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

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

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

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

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

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

null :: LinearExpression a a0 -> Bool #

length :: LinearExpression a a0 -> Int #

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

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

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

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

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

Traversable (LinearExpression a) Source #

Useful for substituting values in a monadic/applicative context

Instance details

Defined in Math.Programming.Types

Methods

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

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

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

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

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

Defined in Math.Programming.Types

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

Defined in Math.Programming.Types

Num a => Semigroup (LinearExpression a b) Source #

Implements addition of 'LinearExpression a b' terms

Instance details

Defined in Math.Programming.Types

Num a => Monoid (LinearExpression a b) Source #

Using '0' as the identity element

Instance details

Defined in Math.Programming.Types

data Inequality a Source #

Non-strict inequalities.

Constructors

Inequality Ordering a a 
Instances
Functor Inequality Source # 
Instance details

Defined in Math.Programming.Types

Methods

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

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

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 #

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) #

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