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

Copyright(C) 2013 Adam Vogt
MaintainerAdam Vogt <vogt.adam@gmail.com>
Stabilityunstable
Safe HaskellNone
LanguageHaskell2010

Ipopt.Raw

Contents

Description

Description: lowest-level parts of the binding

Synopsis

specifying problem

createIpoptProblemAD Source

Arguments

:: Vec

xL Vector of lower bounds for decision variables with length n

-> Vec

xU Vector of upper bounds for decision variables

-> Vec

gL Vector of lower bounds for constraint functions g(x) with length m

-> Vec

gU Vector of upper bounds for constraint functions g(x)

-> (forall a. AnyRFCxt a => V.Vector a -> a)

objective function f : R^n -> R

-> (forall a. AnyRFCxt a => V.Vector a -> V.Vector a)

constraint functions g : R^n -> R^m

-> IO IpProblem 

Set-up an IpProblem to be solved later. Only objective function (f) and constraint functions (g) need to be specified. Derivatives needed by ipopt are computed by Numeric.AD.

To solve the optimization problem:

             min f(x)
  such that
          xL <=  x     <= xU
          gL <=  g(x)  <= gU

First create an opaque IpProblem object (nlp):

nlp <- createIpOptProblemAD xL xU gL gU f g

Then pass it off to ipoptSolve.

ipoptSolve nlp x0

Refer to examples/HS71ad.hs for details of setting up the vectors supplied.

createIpoptProblemADSparse Source

Arguments

:: Vec

xL Vector of lower bounds for decision variables with length n

-> Vec

xU Vector of upper bounds for decision variables

-> Vec

gL Vector of lower bounds for constraint functions g(x) with length m

-> Vec

gU Vector of upper bounds for constraint functions g(x)

-> (V.Vector (Sparse.Sparse C2HSImp.CDouble) -> Sparse.Sparse C2HSImp.CDouble)

objective function f : R^n -> R

-> (V.Vector (Sparse.Sparse C2HSImp.CDouble) -> V.Vector (Sparse.Sparse C2HSImp.CDouble))

constraint functions g : R^n -> R^m

-> IO IpProblem 

this is 50% slower than createIpoptProblemAD in one instance http://code.haskell.org/~aavogt/ipopt-hs/examples/bench.html#williams-otto-process). But the benefit is that no RankN types are used (so it is possible to implement more functions without having to modify AnyRFCxt)

solve

ipoptSolve Source

Arguments

:: VG.Vector v Double 
=> IpProblem 
-> Vec

starting point x. Note that the value is overwritten with the final x.

-> IO (IpOptSolved v) 

solver options

types

type Vec = VM.IOVector Double Source

Vector of numbers

type IntermediateCB Source

Arguments

 = C2HSImp.CInt

alg_mod (0 regular, 1 is resto)

-> C2HSImp.CInt

iter count

-> Double

obj value

-> Double

inf_pr

-> Double

inf_du

-> Double

mu

-> Double

d_norm

-> Double

regularization_size

-> Double

alpha_du

-> Double

alpha_pr

-> C2HSImp.CInt

ls_trials

-> C2HSImp.Ptr ()

user_data (usually null)

-> IO IpBool 

lower-level parts of the binding

createIpoptProblem :: Vec -> Vec -> Vec -> Vec -> Int -> Int -> IpF -> IpG -> IpGradF -> IpJacG -> IpH -> IO IpProblem Source

marshalling functions

wrapIpF1 :: UnFunPtr IpF -> IO IpF Source

wrapIpG1 :: UnFunPtr IpG -> IO IpG Source

wrapIpH1 :: UnFunPtr IpH -> IO IpH Source

wrapIpF2 :: (Integral a2, Storable a, Storable a1) => (VM.MVector s a1 -> IO a) -> a2 -> C2HSImp.Ptr a1 -> t -> C2HSImp.Ptr a -> t1 -> IO IpBool Source

wrapIpGradF2 :: (Integral a2, Storable a, Storable a1) => (VM.MVector s a1 -> IO (VM.MVector RealWorld a)) -> a2 -> C2HSImp.Ptr a1 -> t -> C2HSImp.Ptr a -> t1 -> IO IpBool Source

wrapIpG2 :: (Integral a1, Integral a3, Storable a, Storable a2) => (VM.MVector s a2 -> IO (VM.MVector RealWorld a)) -> a3 -> C2HSImp.Ptr a2 -> t -> a1 -> C2HSImp.Ptr a -> t1 -> IO IpBool Source

wrapIpJacG2 :: (Integral a3, Integral a5, Storable a, Storable a1, Storable a2, Storable a4) => (VM.MVector s a -> VM.MVector s1 a1 -> IO b) -> (VM.MVector s2 a2 -> VM.MVector s3 a4 -> IO b1) -> a3 -> C2HSImp.Ptr a2 -> t -> t1 -> a5 -> C2HSImp.Ptr a -> C2HSImp.Ptr a1 -> C2HSImp.Ptr a4 -> t2 -> IO IpBool Source

wrapIpH2 :: (Integral a1, Integral a3, Integral a7, Storable a, Storable a2, Storable a4, Storable a5, Storable a6) => (VM.MVector s3 a5 -> VM.MVector s4 a6 -> IO b1) -> (t3 -> VM.MVector s a -> VM.MVector s1 a2 -> VM.MVector s2 a4 -> IO b) -> a3 -> C2HSImp.Ptr a2 -> t -> t3 -> a1 -> C2HSImp.Ptr a -> t1 -> a7 -> C2HSImp.Ptr a5 -> C2HSImp.Ptr a6 -> C2HSImp.Ptr a4 -> t2 -> IO IpBool Source