glpk-hs-0.0.4: Comprehensive GLPK linear programming bindings

Data.LinearProgram.LPMonad

Contents

Description

A collection of operations that can be used to specify linear programming in a simple, monadic way. It is not too difficult to construct LP values explicitly, but this module may help simplify and modularize the construction of the linear program, for example separating different families of constraints in the problem specification.

Many of these functions should be executed in either the LPM v c or the LPT v c IO monad.

Synopsis

Monad definitions

type LPM v c = LPT v c IdentitySource

A simple monad for constructing linear programs. This library is intended to be able to link to a variety of different linear programming implementations.

type LPT v c = StateT (LP v c)Source

A simple monad transformer for constructing linear programs in an arbitrary monad.

runLPM :: (Ord v, Module r c) => LPM v c a -> (a, LP v c)Source

runLPT :: (Ord v, Module r c) => LPT v c m a -> m (a, LP v c)Source

execLPM :: (Ord v, Module r c) => LPM v c a -> LP v cSource

Constructs a linear programming problem.

execLPT :: (Ord v, Module r c, Monad m) => LPT v c m a -> m (LP v c)Source

Constructs a linear programming problem in the specified monad.

evalLPM :: (Ord v, Module r c) => LPM v c a -> aSource

Runs the specified operation in the linear programming monad.

evalLPT :: (Monad m, Ord v, Module r c) => LPT v c m a -> m aSource

Runs the specified operation in the linear programming monad transformer.

Objective configuration

setDirection :: MonadState (LP v c) m => Direction -> m ()Source

Sets the optimization direction of the linear program: maximization or minimization.

setObjective :: MonadState (LP v c) m => LinFunc v c -> m ()Source

Sets the objective function, overwriting the previous objective function.

addObjective :: (Ord v, Module r c, MonadState (LP v c) m) => LinFunc v c -> m ()Source

Adds this function to the objective function.

addWeightedObjective :: (Ord v, Module r c, MonadState (LP v c) m) => r -> LinFunc v c -> m ()Source

Adds this function to the objective function, with the specified weight. Equivalent to addObjective (wt *^ obj).

Two-function constraints

leq :: (Ord v, Module r c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()Source

Specifies the relationship between two functions in the variables.

equal :: (Ord v, Module r c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()Source

geq :: (Ord v, Module r c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()Source

leq' :: (Ord v, Module r c, MonadState (LP v c) m) => String -> LinFunc v c -> LinFunc v c -> m ()Source

Specifies the relationship between two functions in the variables, with a label on the constraint.

equal' :: (Ord v, Module r c, MonadState (LP v c) m) => String -> LinFunc v c -> LinFunc v c -> m ()Source

geq' :: (Ord v, Module r c, MonadState (LP v c) m) => String -> LinFunc v c -> LinFunc v c -> m ()Source

One-function constraints

leqTo :: MonadState (LP v c) m => LinFunc v c -> c -> m ()Source

Sets a constraint on a linear function in the variables.

equalTo :: MonadState (LP v c) m => LinFunc v c -> c -> m ()Source

geqTo :: MonadState (LP v c) m => LinFunc v c -> c -> m ()Source

constrain :: MonadState (LP v c) m => LinFunc v c -> Bounds c -> m ()Source

The most general form of an unlabeled constraint.

leqTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()Source

Sets a labelled constraint on a linear function in the variables.

equalTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()Source

geqTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()Source

constrain' :: MonadState (LP v c) m => String -> LinFunc v c -> Bounds c -> m ()Source

The most general form of a labeled constraint.

Variable constraints

varLeq :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> m ()Source

Sets a constraint on the value of a variable. If you constrain a variable more than once, the constraints will be combined.

varEq :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> m ()Source

varGeq :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> m ()Source

varBds :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> c -> m ()Source

Bounds the value of a variable on both sides. If you constrain a variable more than once, the constraints will be combined.

setVarBounds :: (Ord v, Ord c, MonadState (LP v c) m) => v -> Bounds c -> m ()Source

The most general way to set constraints on a variable. If you constrain a variable more than once, the constraints will be combined.

setVarKind :: (Ord v, MonadState (LP v c) m) => v -> VarKind -> m ()Source

Sets the kind ('type') of a variable. See VarKind.

Solvers

quickSolveMIP :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => m (ReturnCode, Maybe (Double, Map v Double))Source

Solves the linear program with the default settings in GLPK. Returns the return code, and if the solver was successful, the objective function value and the settings of each variable.

glpSolve :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => GLPOpts -> m (ReturnCode, Maybe (Double, Map v Double))Source

Solves the linear program with the specified options in GLPK. Returns the return code, and if the solver was successful, the objective function value and the settings of each variable.

quickSolveMIP' :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => m (ReturnCode, Maybe (Double, Map v Double, [RowValue v c]))Source

Solves the linear program with the default settings in GLPK. Returns the return code, and if the solver was successful, the objective function value, the settings of each variable, and the value of each constraint/row.

glpSolve' :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => GLPOpts -> m (ReturnCode, Maybe (Double, Map v Double, [RowValue v c]))Source

Solves the linear program with the specified options in GLPK. Returns the return code, and if the solver was successful, the objective function value, the settings of each variable, and the value of each constraint/row.

File I/O

writeLPToFile :: (Ord v, Show v, Real c, MonadState (LP v c) m, MonadIO m) => FilePath -> m ()Source