Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- type Expr m = LinearExpression (Numeric m) (Variable m)
- class (Monad m, Show (Numeric m), RealFrac (Numeric m)) => LPMonad m where
- type Numeric m :: *
- data Variable m :: *
- data Constraint m :: *
- data Objective m :: *
- addVariable :: m (Variable m)
- removeVariable :: Variable m -> m ()
- getVariableName :: Variable m -> m String
- setVariableName :: Variable m -> String -> m ()
- getVariableBounds :: Variable m -> m (Bounds (Numeric m))
- setVariableBounds :: Variable m -> Bounds (Numeric m) -> m ()
- getVariableValue :: Variable m -> m (Numeric m)
- addConstraint :: Inequality (LinearExpression (Numeric m) (Variable m)) -> m (Constraint m)
- removeConstraint :: Constraint m -> m ()
- getConstraintName :: Constraint m -> m String
- setConstraintName :: Constraint m -> String -> m ()
- getDualValue :: Constraint m -> m (Numeric m)
- addObjective :: LinearExpression (Numeric m) (Variable m) -> m (Objective m)
- getObjectiveName :: Objective m -> m String
- setObjectiveName :: Objective m -> String -> m ()
- getObjectiveSense :: Objective m -> m Sense
- setObjectiveSense :: Objective m -> Sense -> m ()
- getObjectiveValue :: Objective m -> m (Numeric m)
- getTimeout :: m Double
- setTimeout :: Double -> m ()
- optimizeLP :: m SolutionStatus
- class LPMonad m => IPMonad m where
- optimizeIP :: m SolutionStatus
- getVariableDomain :: Variable m -> m Domain
- setVariableDomain :: Variable m -> Domain -> m ()
- getRelativeMIPGap :: m Double
- setRelativeMIPGap :: Double -> m ()
- data Sense
- data SolutionStatus
- = Optimal
- | Feasible
- | Infeasible
- | Unbounded
- | Error
- data Bounds b
- = NonNegativeReals
- | NonPositiveReals
- | Interval b b
- | Free
- data Domain
- = Continuous
- | Integer
- | Binary
- class Nameable m a where
- data LinearExpression a b = LinearExpression [(a, b)] a
- data Inequality a = Inequality Ordering a a
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, Show (Numeric m), RealFrac (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.
The numeric type used in the model.
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.
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.
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.
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.
Whether a math program is minimizing or maximizing its objective.
data SolutionStatus Source #
The outcome of an optimization.
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. |
Instances
Eq SolutionStatus Source # | |
Defined in Math.Programming.Types (==) :: SolutionStatus -> SolutionStatus -> Bool # (/=) :: SolutionStatus -> SolutionStatus -> Bool # | |
Ord SolutionStatus Source # | |
Defined in Math.Programming.Types compare :: SolutionStatus -> SolutionStatus -> Ordering # (<) :: SolutionStatus -> SolutionStatus -> Bool # (<=) :: SolutionStatus -> SolutionStatus -> Bool # (>) :: SolutionStatus -> SolutionStatus -> Bool # (>=) :: SolutionStatus -> SolutionStatus -> Bool # max :: SolutionStatus -> SolutionStatus -> SolutionStatus # min :: SolutionStatus -> SolutionStatus -> SolutionStatus # | |
Read SolutionStatus Source # | |
Defined in Math.Programming.Types readsPrec :: Int -> ReadS SolutionStatus # readList :: ReadS [SolutionStatus] # | |
Show SolutionStatus Source # | |
Defined in Math.Programming.Types showsPrec :: Int -> SolutionStatus -> ShowS # show :: SolutionStatus -> String # showList :: [SolutionStatus] -> ShowS # |
An interval of the real numbers.
NonNegativeReals | The non-negative reals. |
NonPositiveReals | The non-positive reals. |
Interval b b | Any closed interval of the reals. |
Free | Any real number. |
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.
Continuous | The variable lies in the real numbers |
Integer | The variable lies in the integers |
Binary | The variable lies in the set |
data LinearExpression a b Source #
A linear expression containing symbolic variables of type b
and
numeric coefficients of type a
.
Using String
s to denote variables and Double
s as our numeric
type, we could express 3 x + 2 y + 1 as
LinearExpression [(3, "x"), (2, "y")] 1
LinearExpression [(a, b)] a |
Instances
data Inequality a Source #
Non-strict inequalities.
Inequality Ordering a a |