Safe Haskell | None |
---|
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
or the LPM
v c
monad.
If you wish to generate new variables on an ad-hoc basis, rather than supplying your own variable type, use the
LPT
v c IO
VSupply
or VSupplyT
monads in your transformer stack, as in
or
LPT
Var
c VSupply
. To generate new variables, use LPT
Var
c (VSupplyT
IO
)supplyNew
or supplyN
.
- type LPM v c = LPT v c Identity
- type LPT v c = StateT (LP v c)
- runLPM :: (Ord v, Group c) => LPM v c a -> (a, LP v c)
- runLPT :: (Ord v, Group c) => LPT v c m a -> m (a, LP v c)
- execLPM :: (Ord v, Group c) => LPM v c a -> LP v c
- execLPT :: (Ord v, Group c, Monad m) => LPT v c m a -> m (LP v c)
- evalLPM :: (Ord v, Group c) => LPM v c a -> a
- evalLPT :: (Ord v, Group c, Monad m) => LPT v c m a -> m a
- setDirection :: MonadState (LP v c) m => Direction -> m ()
- setObjective :: MonadState (LP v c) m => LinFunc v c -> m ()
- addObjective :: (Ord v, Group c, MonadState (LP v c) m) => LinFunc v c -> m ()
- addWeightedObjective :: (Ord v, Module r c, MonadState (LP v c) m) => r -> LinFunc v c -> m ()
- leq :: (Ord v, Group c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()
- equal :: (Ord v, Group c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()
- geq :: (Ord v, Group c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()
- leq' :: (Ord v, Group c, MonadState (LP v c) m) => String -> LinFunc v c -> LinFunc v c -> m ()
- equal' :: (Ord v, Group c, MonadState (LP v c) m) => String -> LinFunc v c -> LinFunc v c -> m ()
- geq' :: (Ord v, Group c, MonadState (LP v c) m) => String -> LinFunc v c -> LinFunc v c -> m ()
- leqTo :: MonadState (LP v c) m => LinFunc v c -> c -> m ()
- equalTo :: MonadState (LP v c) m => LinFunc v c -> c -> m ()
- geqTo :: MonadState (LP v c) m => LinFunc v c -> c -> m ()
- constrain :: MonadState (LP v c) m => LinFunc v c -> Bounds c -> m ()
- leqTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()
- equalTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()
- geqTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()
- constrain' :: MonadState (LP v c) m => String -> LinFunc v c -> Bounds c -> m ()
- varLeq :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> m ()
- varEq :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> m ()
- varGeq :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> m ()
- varBds :: (Ord v, Ord c, MonadState (LP v c) m) => v -> c -> c -> m ()
- setVarBounds :: (Ord v, Ord c, MonadState (LP v c) m) => v -> Bounds c -> m ()
- setVarKind :: (Ord v, MonadState (LP v c) m) => v -> VarKind -> m ()
- module Control.Monad.LPMonad.Supply
- quickSolveMIP :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => m (ReturnCode, Maybe (Double, Map v Double))
- quickSolveLP :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => m (ReturnCode, Maybe (Double, Map v Double))
- glpSolve :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => GLPOpts -> m (ReturnCode, Maybe (Double, Map v Double))
- quickSolveMIP' :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => m (ReturnCode, Maybe (Double, Map v Double, [RowValue v c]))
- quickSolveLP' :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => m (ReturnCode, Maybe (Double, Map v Double, [RowValue v c]))
- glpSolve' :: (Ord v, Real c, MonadState (LP v c) m, MonadIO m) => GLPOpts -> m (ReturnCode, Maybe (Double, Map v Double, [RowValue v c]))
- writeLPToFile :: (Ord v, Show v, Real c, MonadState (LP v c) m, MonadIO m) => FilePath -> m ()
- readLPFromFile :: (Ord v, Read v, Fractional c, MonadState (LP v c) m, MonadIO m) => FilePath -> m ()
- readLPFromFile' :: (MonadState (LP String Double) m, MonadIO m) => FilePath -> m ()
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.
execLPT :: (Ord v, Group 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, Group c) => LPM v c a -> aSource
Runs the specified operation in the linear programming monad.
evalLPT :: (Ord v, Group c, Monad m) => LPT v c m a -> m aSource
Runs the specified operation in the linear programming monad transformer.
Constructing the LP
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, Group 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, Group c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()Source
Specifies the relationship between two functions in the variables. So, for example,
equal (f ^+^ g) h
constrains the value of h
to be equal to the value of f
plus the value of g
.
equal :: (Ord v, Group c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()Source
Specifies the relationship between two functions in the variables. So, for example,
equal (f ^+^ g) h
constrains the value of h
to be equal to the value of f
plus the value of g
.
geq :: (Ord v, Group c, MonadState (LP v c) m) => LinFunc v c -> LinFunc v c -> m ()Source
Specifies the relationship between two functions in the variables. So, for example,
equal (f ^+^ g) h
constrains the value of h
to be equal to the value of f
plus the value of g
.
leq' :: (Ord v, Group 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, Group 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.
geq' :: (Ord v, Group 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.
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
Sets a constraint on a linear function in the variables.
geqTo :: MonadState (LP v c) m => LinFunc v c -> c -> m ()Source
Sets a constraint on a linear function in the variables.
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 labeled constraint on a linear function in the variables.
equalTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()Source
Sets a labeled constraint on a linear function in the variables.
geqTo' :: MonadState (LP v c) m => String -> LinFunc v c -> c -> m ()Source
Sets a labeled constraint on a linear function in the variables.
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. If the constraints are mutually contradictory, an error will be generated. This is more efficient than adding an equivalent function constraint.
varEq :: (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. If the constraints are mutually contradictory, an error will be generated. This is more efficient than adding an equivalent function constraint.
varGeq :: (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. If the constraints are mutually contradictory, an error will be generated. This is more efficient than adding an equivalent function constraint.
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. If the constraints are mutually contradictory, an error will be generated. This is more efficient than adding an equivalent function constraint.
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. If you combine mutually contradictory constraints, an error will be generated. This is more efficient than creating an equivalent function constraint.
setVarKind :: (Ord v, MonadState (LP v c) m) => v -> VarKind -> m ()Source
Sets the kind ('type') of a variable. See VarKind
.
Generation of new variables
module Control.Monad.LPMonad.Supply
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.
quickSolveLP :: (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.
quickSolveLP' :: (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
Writes the current linear program to the specified file in CPLEX LP format. (This is a binding to GLPK, not a Haskell implementation of CPLEX.)
readLPFromFile :: (Ord v, Read v, Fractional c, MonadState (LP v c) m, MonadIO m) => FilePath -> m ()Source
Reads a linear program from the specified file in CPLEX LP format, overwriting
the current linear program. Uses read
and realToFrac
to translate to the specified type.
Warning: this may not work on all files written using writeLPToFile
, since variable names
may be changed.
(This is a binding to GLPK, not a Haskell implementation of CPLEX.)
readLPFromFile' :: (MonadState (LP String Double) m, MonadIO m) => FilePath -> m ()Source
Reads a linear program from the specified file in CPLEX LP format, overwriting the current linear program. (This is a binding to GLPK, not a Haskell implementation of CPLEX.)