comfort-glpk-0.0.0.1: Linear Programming using GLPK and comfort-array

Safe HaskellNone
LanguageHaskell98

Numeric.GLPK

Description

The following LP problem

maximize 4 x_1 - 3 x_2 + 2 x_3 subject to

2 x_1 + x_2 <= 10
x_2 + 5 x_3 <= 20

and

x_i >= 0

is used as an example in the doctest comments.

By default all indeterminates are non-negative. A given bound for a variable completely replaces the default, so 0 <= x_i <= b must be explicitly given as i >=<. (0,b). Multiple bounds for a variable are not allowed, instead of [i >=. a, i <=. b] use i >=<. (a,b).

Synopsis

Documentation

data Term ix Source #

Constructors

Term Double ix 
Instances
Show ix => Show (Term ix) Source # 
Instance details

Defined in Numeric.GLPK

Methods

showsPrec :: Int -> Term ix -> ShowS #

show :: Term ix -> String #

showList :: [Term ix] -> ShowS #

data Bound Source #

Instances
Show Bound Source # 
Instance details

Defined in Numeric.GLPK

Methods

showsPrec :: Int -> Bound -> ShowS #

show :: Bound -> String #

showList :: [Bound] -> ShowS #

data Inequality x Source #

Constructors

Inequality x Bound 
Instances
Functor Inequality Source # 
Instance details

Defined in Numeric.GLPK

Methods

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

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

Show x => Show (Inequality x) Source # 
Instance details

Defined in Numeric.GLPK

(<=.) :: x -> Double -> Inequality x infix 4 Source #

(>=.) :: x -> Double -> Inequality x infix 4 Source #

(==.) :: x -> Double -> Inequality x infix 4 Source #

(>=<.) :: x -> (Double, Double) -> Inequality x infix 4 Source #

data NoSolutionType Source #

Instances
Eq NoSolutionType Source # 
Instance details

Defined in Numeric.GLPK

Show NoSolutionType Source # 
Instance details

Defined in Numeric.GLPK

NFData NoSolutionType Source # 
Instance details

Defined in Numeric.GLPK

Methods

rnf :: NoSolutionType -> () #

data SolutionType Source #

Constructors

Feasible 
Infeasible 
Optimal 
Instances
Eq SolutionType Source # 
Instance details

Defined in Numeric.GLPK

Show SolutionType Source # 
Instance details

Defined in Numeric.GLPK

NFData SolutionType Source # 
Instance details

Defined in Numeric.GLPK

Methods

rnf :: SolutionType -> () #

data Direction Source #

Constructors

Minimize 
Maximize 

type Bounds ix = [Inequality ix] Source #

(.*) :: Double -> ix -> Term ix infix 7 Source #

objectiveFromTerms :: (Indexed sh, Index sh ~ ix) => sh -> [Term ix] -> Objective sh Source #

simplex :: (Indexed sh, Index sh ~ ix) => Bounds ix -> Constraints ix -> (Direction, Objective sh) -> Solution sh Source #

>>> case Shape.indexTupleFromShape tripletShape of (x1,x2,x3) -> mapSnd (mapSnd Array.toTuple) <$> LP.simplex [] [[2.*x1, 1.*x2] <=. 10, [1.*x2, 5.*x3] <=. 20] (LP.Maximize, Array.fromTuple (4,-3,2) :: Array.Array TripletShape Double)
Right (Optimal,(28.0,(5.0,0.0,4.0)))
\(QC.Positive posWeight) (QC.Positive negWeight) target -> case Shape.indexTupleFromShape pairShape of (pos,neg) -> case mapSnd (mapSnd Array.toTuple) <$> LP.simplex [] [[1.*pos, (-1).*neg] ==. target] (LP.Minimize, Array.fromTuple (posWeight,negWeight) :: Array.Array PairShape Double) of (Right (LP.Optimal,(absol,(posResult,negResult)))) -> QC.property (absol>=0) .&&. (posResult === 0 .||. negResult === 0); _ -> QC.property False

simplexMulti :: (Indexed sh, Index sh ~ ix) => Bounds ix -> Constraints ix -> sh -> T [] (Direction, [Term ix]) -> ([Double], Solution sh) Source #

Optimize for one objective after another. That is, if the first optimization succeeds then the optimum is fixed as constraint and the optimization is continued with respect to the second objective and so on. The iteration fails if one optimization fails. The obtained objective values are returned as well. Their number equals the number of attempted optimizations.

The last objective value is included in the Solution value. This is a bit inconsistent, but this way you have a warranty that there is an objective value if the optimization is successful.

The objectives are expected as Terms because after successful optimization step they are used as (sparse) constraints. It's also easy to assert that the same array shape is used for all objectives.

The function does not work reliably, because an added objective can make the system infeasible due to rounding errors. E.g. a non-negative objective can become very small but negative.

exact :: (Indexed sh, Index sh ~ ix) => Bounds ix -> Constraints ix -> (Direction, Objective sh) -> Solution sh Source #

>>> case Shape.indexTupleFromShape tripletShape of (x1,x2,x3) -> mapSnd (mapSnd Array.toTuple) <$> LP.exact [] [[2.*x1, 1.*x2] <=. 10, [1.*x2, 5.*x3] <=. 20] (LP.Maximize, Array.fromTuple (4,-3,2) :: Array.Array TripletShape Double)
Right (Optimal,(28.0,(5.0,0.0,4.0)))

interior :: (Indexed sh, Index sh ~ ix) => Bounds ix -> Constraints ix -> (Direction, Objective sh) -> Solution sh Source #

>>> case Shape.indexTupleFromShape tripletShape of (x1,x2,x3) -> mapSnd (mapPair (round3, Array.toTuple . Array.map round3)) <$> LP.interior [] [[2.*x1, 1.*x2] <=. 10, [1.*x2, 5.*x3] <=. 20] (LP.Maximize, Array.fromTuple (4,-3,2) :: Array.Array TripletShape Double)
Right (Optimal,(28.0,(5.0,0.0,4.0)))

interiorMulti :: (Indexed sh, Index sh ~ ix) => Bounds ix -> Constraints ix -> sh -> T [] (Direction, [Term ix]) -> ([Double], Solution sh) Source #

Optimize for one objective after another. That is, if the first optimization succeeds then the optimum is fixed as constraint and the optimization is continued with respect to the second objective and so on. The iteration fails if one optimization fails. The obtained objective values are returned as well. Their number equals the number of attempted optimizations.

The last objective value is included in the Solution value. This is a bit inconsistent, but this way you have a warranty that there is an objective value if the optimization is successful.

The objectives are expected as Terms because after successful optimization step they are used as (sparse) constraints. It's also easy to assert that the same array shape is used for all objectives.

The function does not work reliably, because an added objective can make the system infeasible due to rounding errors. E.g. a non-negative objective can become very small but negative.