highs-lp-0.0: Linear Programming using HiGHS and comfort-array
Safe HaskellSafe-Inferred
LanguageHaskell98

Numeric.HiGHS.LP.Monad

Description

The monadic interface to CLP allows to optimize with respect to multiple objectives, successively.

Synopsis

simple solver with warm restart

data T sh a Source #

Instances

Instances details
Applicative (T sh) Source # 
Instance details

Defined in Numeric.HiGHS.LP.Monad

Methods

pure :: a -> T sh a #

(<*>) :: T sh (a -> b) -> T sh a -> T sh b #

liftA2 :: (a -> b -> c) -> T sh a -> T sh b -> T sh c #

(*>) :: T sh a -> T sh b -> T sh b #

(<*) :: T sh a -> T sh b -> T sh a #

Functor (T sh) Source # 
Instance details

Defined in Numeric.HiGHS.LP.Monad

Methods

fmap :: (a -> b) -> T sh a -> T sh b #

(<$) :: a -> T sh b -> T sh a #

Monad (T sh) Source # 
Instance details

Defined in Numeric.HiGHS.LP.Monad

Methods

(>>=) :: T sh a -> (a -> T sh b) -> T sh b #

(>>) :: T sh a -> T sh b -> T sh b #

return :: a -> T sh a #

run :: (Indexed sh, Index sh ~ ix) => sh -> Bounds ix -> T sh a -> a Source #

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; _ -> False
forAllMethod $ \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) objs
forAllMethod $ \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)

data Method Source #

Instances

Instances details
Show Method Source # 
Instance details

Defined in Numeric.HiGHS.LP.Private

data ModelStatus Source #

Instances

Instances details
Show ModelStatus Source # 
Instance details

Defined in Numeric.HiGHS.LP.Enumeration

Eq ModelStatus Source # 
Instance details

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 #

data Query sh a Source #

Instances

Instances details
Applicative (Query sh) Source # 
Instance details

Defined in Numeric.HiGHS.LP.Private

Methods

pure :: a -> Query sh a #

(<*>) :: Query sh (a -> b) -> Query sh a -> Query sh b #

liftA2 :: (a -> b -> c) -> Query sh a -> Query sh b -> Query sh c #

(*>) :: Query sh a -> Query sh b -> Query sh b #

(<*) :: Query sh a -> Query sh b -> Query sh a #

Functor (Query sh) Source # 
Instance details

Defined in Numeric.HiGHS.LP.Private

Methods

fmap :: (a -> b) -> Query sh a -> Query sh b #

(<$) :: a -> Query sh b -> Query sh a #

Monad (Query sh) Source # 
Instance details

Defined in Numeric.HiGHS.LP.Private

Methods

(>>=) :: Query sh a -> (a -> Query sh b) -> Query sh b #

(>>) :: Query sh a -> Query sh b -> Query sh b #

return :: a -> Query sh a #

getSolutionVectors :: C sh => Query sh ((Array sh Double, Array sh Double), (Array ShapeInt Double, Array ShapeInt Double)) Source #