ipopt-hs-0.4.0.1: haskell binding to ipopt and nlopt including automatic differentiation

Safe HaskellNone

Ipopt.NLP

Contents

Description

see usage in examples/Test3.hs (and other examples)

IPOPT does support naming variables if you use c++ (by overriding a virtual void finalize_metadata), but it's not clear that we can set that from c/haskell

Synopsis

state

data NLPFun Source

Constructors

NLPFun 

Instances

data NLPState Source

Constructors

NLPState 

Fields

_nMax :: Ix

current maximum index

_currentEnv :: [String]

what namespace are we currently in (see inEnv)

_variables :: Map String Ix

fully qualified (see inEnv) name

_variablesInv :: IxMap String

invert _variables

_constraintLabels :: IntMap String

human-readable descriptions for the constraint, objective and variables

_objLabels :: IntMap String

human-readable descriptions for the constraint, objective and variables

_varLabels :: IxMap String
 
_varEnv :: IxMap (Set [String])

in what environments is a given var used?

_constraintEnv :: IntMap [String]
 
_objEnv :: IntMap [String]
 
_nlpfun :: NLPFun
 
_defaultBounds :: (Double, Double)

the default (xL,xU) for xL < x < xU

_defaultConstraintTol :: (Double, Double)

for nlopt (lower/upper)

_constraintTol :: Seq (Double, Double)
 
_initX :: Vector Double

inital state variable for the solver

Instances

newtype IxMap a Source

Constructors

IxMap (IntMap a) 

Instances

newtype Ix Source

the solver deals with arrays. This type is for indexes into the array for the current variables that the solver is trying to find.

Constructors

Ix 

Fields

_varIx :: Int
 

Instances

nlpstate0 :: NLPStateSource

the initial state to use when you actually have to get to IO with the solution

low level lenses to NLPState

ixMap :: forall a a. Iso (IntMap a) (IntMap a) (IxMap a) (IxMap a)Source

ix_ :: Applicative f => Ix -> (a -> f a) -> IxMap a -> f (IxMap a)Source

should be a way to write an instance of At that'll make the normal atix work with the IxMap Ix (as opposed to IntMap/Int)

at_ :: Functor f => Ix -> (Maybe a -> f (Maybe a)) -> IxMap a -> f (IxMap a)Source

addDesc :: MonadState s m => Setting (->) s s (IntMap a) (IntMap a) -> Maybe a -> Key -> m ()Source

high-level functions

solveNLP'Source

Arguments

:: (Vector v Double, MonadIO m) 
=> (IpProblem -> IO ())

set ipopt options (using functions from Ipopt.Raw)

-> NLPT m (IpOptSolved v) 

calls createIpoptProblemAD and ipoptSolve. To be used at the end of a do-block.

addGSource

Arguments

:: Monad m 
=> Maybe String

optional description

-> (Double, Double)

bounds (gl,gu) for the single inequality gl_i <= g_i(x) <= gu_i

-> AnyRF Identity
g_i(x)
-> NLPT m () 

add a constraint

addFSource

Arguments

:: Monad m 
=> Maybe String

description

-> AnyRF Identity

`f_i(x)`

-> NLPT m () 

add a piece of the objective function, which is added in the form `f_1 + f_2 + ...`, to make it easier to understand (at some point) which components are responsible for the majority of the cost, and which are irrelevant.

var'Source

Arguments

:: (Monad m, Functor m) 
=> Maybe (Double, Double)

bounds (xl,xu) to request that xl <= x <= xu. if Nothing, you get whatever is in defaultBounds

-> Maybe String

optional longer description

-> String

variable name (namespace from the pushEnv / popEnv can make an x you request here different from one you previously requested

-> NLPT m Ix

the index (into the rawvector of variables that the solver sees)

add a variable, or get a reference to the the same variable if it has already been used

var :: (Monad m, Functor m) => Maybe (Double, Double) -> String -> StateT NLPState m (AnyRF Identity)Source

a combination of var' and ixToVar

varFresh' :: (Monad m, Functor m) => Maybe (Double, Double) -> String -> NLPT m IxSource

var, except this causes the solver to get a new variable, so that you can use:

 [a,b,c,d,e] <- replicateM 5 (varFresh (Just (0, 10)) "x")

and the different letters can take different values (between 0 and 10) in the optimal solution (depending on what you do with a and similar in the objective function and other constraints).

namespace

When you build up an optimization problem, it may be composed of pieces. Functions in this section help to ease the pain of making unique variables. To illustrate:

 m <- inEnv "A" (var b "x")
 n <- var b "A.x" 

m and n above should refer to the same variable. In some sense this is "better" that using varFresh all the time, since perhaps you would like to add dependencies between components (say the size of a header pipe, refridgeration unit, foundation etc. has to satisfy sizes of individual components).

inEnv :: Monad m => String -> NLPT m a -> NLPT m aSource

combination of pushEnv and popEnv

pushEnv :: Monad m => String -> NLPT m ()Source

piecewise linear

see for example chapter 20 of http://www.ampl.com/BOOK/download.html and use of the splines package in examples/Test4 and examples/Test5

splitVarSource

Arguments

:: (Monad m, Functor m) 
=> Double
b
-> Ix

index for x

-> NLPT m (AnyRF Identity, AnyRF Identity)
(b-x)_+, (x-b)_+

splits a variable x into two positive variables such that x = x^+ - x^- the new variables represent the positive and negative parts of x - b

 (xMinus, xPlus) <- splitVar b x

Using max (x-b) 0 instead of xPlus (ie. not telling the solver that b is a special point) seems to work just as well

bounds

setBounds :: Monad m => Ix -> (Double, Double) -> NLPT m ()Source

override bounds. Should be unnecessary given var takes bounds.

narrowBounds :: Monad m => Ix -> (Double, Double) -> NLPT m ()Source

shrink the interval in which that variable is allowed.

internal