ipopt-hs-0.2.0.0: haskell binding to ipopt including automatic differentiation

Safe HaskellNone

Ipopt.NLP

Contents

Description

see usage in examples/Test3.hs

Synopsis

state

data NLPFun Source

Constructors

NLPFun 

Instances

data NLPState Source

Constructors

NLPState 

Fields

_nMax :: Ix

current maximum index

_currentEnv :: [String]

what namespace (see inEnv)

_variables :: Map String Ix
 
_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 :: IntMap String

human-readable descriptions for the constraint, objective and variables

_varEnv :: IntMap (Set [String])
 
_constraintEnv :: IntMap [String]
 
_objEnv :: IntMap [String]
 
_nlpfun :: NLPFun
 
_defaultBounds :: (Double, Double)
 
_initX :: Vector Double

inital state variable for the solver

Instances

newtype Ix Source

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

representing functions

data AnyRF cb Source

this wrapper holds functions that can be used for the objective (f) or for constraints (g). Many functions in the instances provided are partial: this seems to be unavoidable because the input variables haven't been decided yet, so you should not be allowed to use compare on these. But for now just use the standard Prelude classes, and unimplementable functions (which would not produce an AnyRF) are calls to error

generate these using var, or perhaps by directly using the constructor: AnyRF $ Identity . V.sum, would for example give the sum of all variables.

Constructors

AnyRF (forall a. RealFloat a => Vector a -> cb a) 

helpers for defining instances

liftOp0 :: (forall a. RealFloat a => a) -> AnyRF IdentitySource

liftOp1 :: (forall a. RealFloat a => a -> a) -> AnyRF Identity -> AnyRF IdentitySource

liftOp2 :: (forall a. RealFloat a => a -> a -> a) -> AnyRF Identity -> AnyRF Identity -> AnyRF IdentitySource

low level lenses to NLPState

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

high-level functions

solveNLP'Source

Arguments

:: MonadIO m 
=> (IpProblem -> IO ())

set ipopt options (using functions from Ipopt.Raw)

-> NLPT m IpOptSolved 

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

-> String

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

-> NLPT m (AnyRF Identity, Ix)

the value, and index (into the raw vector 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

var' without the usually unnecessary Ix

varFresh :: (Monad m, Functor m) => Maybe (Double, Double) -> [Char] -> StateT NLPState m (AnyRF Identity)Source

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).

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

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