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

Math.Programming.Types

Description

Data and class definitions for the core math programming interface.

Synopsis

Documentation

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 #

compose2 :: (c -> d) -> (a -> b -> c) -> a -> b -> d Source #

Function composition involving a 2-argument function.

lift2 :: (MonadTrans t, Monad m) => (a -> b -> m c) -> a -> b -> t m c Source #

Monadic lifting involving a 2-argument function.

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

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

type Expr = LinExpr Double Source #

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