| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell98 |
Numeric.HiGHS.LP.Monad
Description
The monadic interface to CLP allows to optimize with respect to multiple objectives, successively.
Synopsis
- data T sh a
- run :: (Indexed sh, Index sh ~ ix) => sh -> Bounds ix -> T sh a -> a
- solve :: (Eq sh, Indexed sh, Index sh ~ ix) => Method -> Constraints Double ix -> (Direction, Objective sh) -> T sh (Result sh)
- data Direction
- data Method
- simplex :: Method
- choose :: Method
- ipm :: Method
- data ModelStatus
- type Result sh = (ModelStatus, Maybe (Double, Array sh Double))
- solveWith :: (Eq sh, Indexed sh, Index sh ~ ix) => Query sh result -> Method -> Constraints Double ix -> (Direction, Objective sh) -> T sh (ModelStatus, Maybe result)
- data Query sh a
- getObjectiveValue :: Query sh Double
- getOptimalVector :: C sh => Query sh (Array sh Double)
- getSolutionVectors :: C sh => Query sh ((Array sh Double, Array sh Double), (Array ShapeInt Double, Array ShapeInt Double))
- getBasisStatus :: C sh => Query sh (Array sh BasisStatus, Array ShapeInt BasisStatus)
- data BasisStatus
simple solver with warm restart
solve :: (Eq sh, Indexed sh, Index sh ~ ix) => Method -> Constraints Double ix -> (Direction, Objective sh) -> T sh (Result sh) Source #
Add new constraints to an existing problem and run with a new direction and objective.
>>>case Shape.indexTupleFromShape tripletShape of (x,y,z) -> fmap (mapSnd Array.toTuple) $ snd $ LP.run tripletShape [] (LP.solve LP.simplex [[2.*x, 1.*y] <=. 10, [1.*y, (5::Double).*z] <=. 20] (LP.Maximize, Array.fromTuple (4,-3,2) :: Array.Array TripletShape Double))Just (28.0,(5.0,0.0,4.0))
forAllMethod $ \method ->
TestLP.forAllOrigin $ \origin ->
TestLP.forAllProblem origin $ \bounds constrs ->
QC.forAll (TestLP.genObjective origin) $ \(dir,obj) ->
case (CLP.solve method bounds constrs (dir,obj),
LP.run (Array.shape origin) bounds $
LP.solve method constrs (dir,obj)) of
((_, Just (optA,_)), (_, Just (optB,_))) ->
TestLP.approxReal 0.1 optA optB; _ -> FalseforAllMethod $ \method ->
TestLP.forAllOrigin $ \origin ->
TestLP.forAllProblem origin $ \bounds constrs ->
TestLP.forAllObjectives origin $ \objs_ ->
case TestLP.successiveObjectives origin 0.01 objs_ of
(dirObj, objs) ->
either
(\msg -> QC.counterexample (show msg) False)
(const $ QC.property True) $
runSuccessive method (Array.shape origin) bounds (constrs,dirObj) objsforAllMethod $ \method ->
TestLP.forAllOrigin $ \origin ->
TestLP.forAllProblem origin $ \bounds constrs ->
TestLP.forAllObjectives origin $ \objs_ ->
let shape = Array.shape origin in
case TestLP.successiveObjectives origin 0.01 objs_ of
(dirObj, objs) ->
approxSuccession 0.01
(solveSuccessiveWarm method shape bounds (constrs,dirObj) objs)
(solveSuccessiveGen method shape bounds (constrs,dirObj) objs)Instances
| Bounded Direction | |
| Enum Direction | |
Defined in Numeric.LinearProgramming.Common Methods succ :: Direction -> Direction # pred :: Direction -> Direction # fromEnum :: Direction -> Int # enumFrom :: Direction -> [Direction] # enumFromThen :: Direction -> Direction -> [Direction] # enumFromTo :: Direction -> Direction -> [Direction] # enumFromThenTo :: Direction -> Direction -> Direction -> [Direction] # | |
| Show Direction | |
| Eq Direction | |
data ModelStatus Source #
Instances
| Show ModelStatus Source # | |
Defined in Numeric.HiGHS.LP.Enumeration Methods showsPrec :: Int -> ModelStatus -> ShowS # show :: ModelStatus -> String # showList :: [ModelStatus] -> ShowS # | |
| Eq ModelStatus Source # | |
Defined in Numeric.HiGHS.LP.Enumeration | |
solve with extra queries on the result
solveWith :: (Eq sh, Indexed sh, Index sh ~ ix) => Query sh result -> Method -> Constraints Double ix -> (Direction, Objective sh) -> T sh (ModelStatus, Maybe result) Source #
getObjectiveValue :: Query sh Double Source #
getSolutionVectors :: C sh => Query sh ((Array sh Double, Array sh Double), (Array ShapeInt Double, Array ShapeInt Double)) Source #
getBasisStatus :: C sh => Query sh (Array sh BasisStatus, Array ShapeInt BasisStatus) Source #
data BasisStatus Source #
Instances
| Storable BasisStatus Source # | |
Defined in Numeric.HiGHS.LP.FFI Methods sizeOf :: BasisStatus -> Int # alignment :: BasisStatus -> Int # peekElemOff :: Ptr BasisStatus -> Int -> IO BasisStatus # pokeElemOff :: Ptr BasisStatus -> Int -> BasisStatus -> IO () # peekByteOff :: Ptr b -> Int -> IO BasisStatus # pokeByteOff :: Ptr b -> Int -> BasisStatus -> IO () # peek :: Ptr BasisStatus -> IO BasisStatus # poke :: Ptr BasisStatus -> BasisStatus -> IO () # | |
| Show BasisStatus Source # | |
Defined in Numeric.HiGHS.LP.FFI Methods showsPrec :: Int -> BasisStatus -> ShowS # show :: BasisStatus -> String # showList :: [BasisStatus] -> ShowS # | |