| Copyright | (c) Matthew Peddie 2017 |
|---|---|
| License | BSD3 |
| Maintainer | Matthew Peddie <mpeddie@gmail.com> |
| Stability | provisional |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Numeric.Optimization.NLOPT.Bindings
Contents
Description
Low-level interface to the NLOPT library. Please see
the NLOPT reference manual
for detailed information; the Haskell functions in this module closely
follow the interface to the C library in nlopt.h.
Differences between this module and the C interface are documented here; functions with identical interfaces are not. In general:
Opt- corresponds to an
nlopt_optobject Result- corresponds to
nlopt_result VectorDouble- corresponds to a
const double *input or adouble *output ScalarFunction- corresponds to
nlopt_func VectorFunction- corresponds to
nlopt_mfunc PreconditionerFunction- corresponds to
nlopt_precond
User data that is handled by void * in the C bindings can be any
Haskell value.
Synopsis
- data Algorithm
- = GN_DIRECT
- | GN_DIRECT_L
- | GN_DIRECT_L_RAND
- | GN_DIRECT_NOSCAL
- | GN_DIRECT_L_NOSCAL
- | GN_DIRECT_L_RAND_NOSCAL
- | GN_ORIG_DIRECT
- | GN_ORIG_DIRECT_L
- | GD_STOGO
- | GD_STOGO_RAND
- | LD_LBFGS_NOCEDAL
- | LD_LBFGS
- | LN_PRAXIS
- | LD_VAR2
- | LD_VAR1
- | LD_TNEWTON
- | LD_TNEWTON_RESTART
- | LD_TNEWTON_PRECOND
- | LD_TNEWTON_PRECOND_RESTART
- | GN_CRS2_LM
- | GN_MLSL
- | GD_MLSL
- | GN_MLSL_LDS
- | GD_MLSL_LDS
- | LD_MMA
- | LN_COBYLA
- | LN_NEWUOA
- | LN_NEWUOA_BOUND
- | LN_NELDERMEAD
- | LN_SBPLX
- | LN_AUGLAG
- | LD_AUGLAG
- | LN_AUGLAG_EQ
- | LD_AUGLAG_EQ
- | LN_BOBYQA
- | GN_ISRES
- | AUGLAG
- | AUGLAG_EQ
- | G_MLSL
- | G_MLSL_LDS
- | LD_SLSQP
- | LD_CCSAQ
- | GN_ESCH
- algorithm_name :: Algorithm -> IO String
- data Result
- isSuccess :: Result -> Bool
- data Opt
- create :: Algorithm -> Word -> IO (Maybe Opt)
- destroy :: Opt -> IO ()
- copy :: Opt -> IO Opt
- srand :: Integral a => a -> IO ()
- srand_time :: IO ()
- data Version = Version {}
- version :: IO Version
- get_algorithm :: Opt -> IO Algorithm
- get_dimension :: Opt -> IO Word
- type ScalarFunction a = Vector Double -> Maybe (IOVector Double) -> a -> IO Double
- type VectorFunction a = Vector Double -> IOVector Double -> Maybe (IOVector Double) -> a -> IO ()
- type PreconditionerFunction a = Vector Double -> Vector Double -> IOVector Double -> a -> IO ()
- data Output = Output {}
- optimize :: Opt -> Vector Double -> IO Output
- set_min_objective :: Opt -> ScalarFunction a -> a -> IO Result
- set_max_objective :: Opt -> ScalarFunction a -> a -> IO Result
- set_precond_min_objective :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> IO Result
- set_precond_max_objective :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> IO Result
- set_lower_bounds :: Opt -> Vector Double -> IO Result
- set_lower_bounds1 :: Opt -> Double -> IO Result
- get_lower_bounds :: Opt -> IO (Vector Double, Result)
- set_upper_bounds :: Opt -> Vector Double -> IO Result
- set_upper_bounds1 :: Opt -> Double -> IO Result
- get_upper_bounds :: Opt -> IO (Vector Double, Result)
- remove_inequality_constraints :: Opt -> IO Result
- add_inequality_constraint :: Opt -> ScalarFunction a -> a -> Double -> IO Result
- add_precond_inequality_constraint :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> Double -> IO Result
- add_inequality_mconstraint :: Opt -> Word -> VectorFunction a -> a -> Double -> IO Result
- remove_equality_constraints :: Opt -> IO Result
- add_equality_constraint :: Opt -> ScalarFunction a -> a -> Double -> IO Result
- add_precond_equality_constraint :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> Double -> IO Result
- add_equality_mconstraint :: Opt -> Word -> VectorFunction a -> a -> Double -> IO Result
- set_stopval :: Opt -> Double -> IO Result
- get_stopval :: Opt -> IO Double
- set_ftol_rel :: Opt -> Double -> IO Result
- get_ftol_rel :: Opt -> IO Double
- set_ftol_abs :: Opt -> Double -> IO Result
- get_ftol_abs :: Opt -> IO Double
- set_xtol_rel :: Opt -> Double -> IO Result
- get_xtol_rel :: Opt -> IO Double
- set_xtol_abs1 :: Opt -> Double -> IO Result
- set_xtol_abs :: Opt -> Vector Double -> IO Result
- get_xtol_abs :: Opt -> IO (Result, Vector Double)
- set_maxeval :: Opt -> Word -> IO Result
- get_maxeval :: Opt -> IO Word
- set_maxtime :: Opt -> Double -> IO Result
- get_maxtime :: Opt -> IO Double
- force_stop :: Opt -> IO Result
- set_force_stop :: Opt -> Word -> IO Result
- get_force_stop :: Opt -> IO Word
- set_local_optimizer :: Opt -> Opt -> IO Result
- set_population :: Opt -> Word -> IO Result
- get_population :: Opt -> IO Word
- set_vector_storage :: Opt -> Word -> IO Result
- get_vector_storage :: Opt -> IO Word
- set_default_initial_step :: Opt -> Vector Double -> IO Result
- set_initial_step :: Opt -> Vector Double -> IO Result
- set_initial_step1 :: Opt -> Double -> IO Result
- get_initial_step :: Opt -> Vector Double -> IO (Result, Vector Double)
C enums
The NLOPT algorithm names, apart from the names of the actual optimization methods, follow this scheme:
G- means a global method
L- means a local method
D- means a method that requires the derivative
N- means a method that does not require the derivative
*_RAND- means the algorithm involves some randomization.
*_NOSCAL- means the algorithm is *not* scaled to a unit hypercube (i.e. it is sensitive to the units of x)
Constructors
| GN_DIRECT | DIviding RECTangles |
| GN_DIRECT_L | DIviding RECTangles, locally-biased variant |
| GN_DIRECT_L_RAND | DIviding RECTangles, "slightly randomized" |
| GN_DIRECT_NOSCAL | DIviding RECTangles, unscaled version |
| GN_DIRECT_L_NOSCAL | DIviding RECTangles, locally-biased and unscaled |
| GN_DIRECT_L_RAND_NOSCAL | DIviding RECTangles, locally-biased, unscaled and "slightly randomized" |
| GN_ORIG_DIRECT | DIviding RECTangles, original FORTRAN implementation |
| GN_ORIG_DIRECT_L | DIviding RECTangles, locally-biased, original FORTRAN implementation |
| GD_STOGO | Stochastic Global Optimization |
| GD_STOGO_RAND | Stochastic Global Optimization, randomized variant |
| LD_LBFGS_NOCEDAL | Limited-memory BFGS |
| LD_LBFGS | Limited-memory BFGS |
| LN_PRAXIS | PRincipal AXIS gradient-free local optimization |
| LD_VAR2 | Shifted limited-memory variable-metric, rank-2 |
| LD_VAR1 | Shifted limited-memory variable-metric, rank-1 |
| LD_TNEWTON | Truncated Newton's method |
| LD_TNEWTON_RESTART | Truncated Newton's method with automatic restarting |
| LD_TNEWTON_PRECOND | Preconditioned truncated Newton's method |
| LD_TNEWTON_PRECOND_RESTART | Preconditioned truncated Newton's method with automatic restarting |
| GN_CRS2_LM | Controlled Random Search with Local Mutation |
| GN_MLSL | Original Multi-Level Single-Linkage |
| GD_MLSL | Original Multi-Level Single-Linkage, user-provided derivative |
| GN_MLSL_LDS | Multi-Level Single-Linkage with Sobol Low-Discrepancy Sequence for starting points |
| GD_MLSL_LDS | Multi-Level Single-Linkage with Sobol Low-Discrepancy Sequence for starting points, user-provided derivative |
| LD_MMA | Method of moving averages |
| LN_COBYLA | Constrained Optimization BY Linear Approximations |
| LN_NEWUOA | Powell's NEWUOA algorithm |
| LN_NEWUOA_BOUND | Powell's NEWUOA algorithm with bounds by SGJ |
| LN_NELDERMEAD | Nelder-Mead Simplex gradient-free method |
| LN_SBPLX | NLOPT implementation of Rowan's Subplex algorithm |
| LN_AUGLAG | AUGmented LAGrangian |
| LD_AUGLAG | AUGmented LAGrangian, user-provided derivative |
| LN_AUGLAG_EQ | AUGmented LAGrangian with penalty functions only for equality constraints |
| LD_AUGLAG_EQ | AUGmented LAGrangian with penalty functions only for equality constraints, user-provided derivative |
| LN_BOBYQA | Bounded Optimization BY Quadratic Approximations |
| GN_ISRES | Improved Stochastic Ranking Evolution Strategy |
| AUGLAG | AUGmented LAGrangian, requires local_optimizer to be set |
| AUGLAG_EQ | AUGmented LAGrangian with penalty functions only for equality constraints, requires local_optimizer to be set |
| G_MLSL | Original Multi-Level Single-Linkage, user-provided derivative, requires local_optimizer to be set |
| G_MLSL_LDS | Multi-Level Single-Linkage with Sobol Low-Discrepancy Sequence for starting points, requires local_optimizer to be set |
| LD_SLSQP | Sequential Least-SQuares Programming |
| LD_CCSAQ | Conservative Convex Separable Approximation |
| GN_ESCH | Evolutionary Algorithm |
Instances
| Bounded Algorithm Source # | |
| Enum Algorithm Source # | |
Defined in Numeric.Optimization.NLOPT.Bindings Methods succ :: Algorithm -> Algorithm # pred :: Algorithm -> Algorithm # fromEnum :: Algorithm -> Int # enumFrom :: Algorithm -> [Algorithm] # enumFromThen :: Algorithm -> Algorithm -> [Algorithm] # enumFromTo :: Algorithm -> Algorithm -> [Algorithm] # enumFromThenTo :: Algorithm -> Algorithm -> Algorithm -> [Algorithm] # | |
| Eq Algorithm Source # | |
| Read Algorithm Source # | |
| Show Algorithm Source # | |
Mostly self-explanatory.
Constructors
| FAILURE | Generic failure code |
| INVALID_ARGS | |
| OUT_OF_MEMORY | |
| ROUNDOFF_LIMITED | |
| FORCED_STOP | |
| SUCCESS | Generic success code |
| STOPVAL_REACHED | |
| FTOL_REACHED | |
| XTOL_REACHED | |
| MAXEVAL_REACHED | |
| MAXTIME_REACHED |
Optimizer object
An optimizer object which must be created, configured and then
passed to optimize to solve a problem
Arguments
| :: Algorithm | Choice of algorithm |
| -> Word | Parameter vector dimension |
| -> IO (Maybe Opt) | Optimizer object |
Create a new Opt object
Random number generator seeding
srand_time :: IO () Source #
Metadata
NLOPT library version, e.g. 2.4.2
Callbacks
type ScalarFunction a Source #
Arguments
| = Vector Double | Parameter vector |
| -> Maybe (IOVector Double) | Gradient vector to be filled in |
| -> a | User data |
| -> IO Double | Scalar result |
This function type corresponds to nlopt_func in C and is used
for scalar functions of the parameter vector. You may pass data of
any type a to the functions in this module that take a
ScalarFunction as an argument; this data will be supplied to your
your function when it is called.
type VectorFunction a Source #
Arguments
| = Vector Double | Parameter vector |
| -> IOVector Double | Output vector to be filled in |
| -> Maybe (IOVector Double) | Gradient vector to be filled in |
| -> a | User data |
| -> IO () |
This function type corresponds to nlopt_mfunc in C and is used
for vector functions of the parameter vector. You may pass data of
any type a to the functions in this module that take a
VectorFunction as an argument; this data will be supplied to your
function when it is called.
type PreconditionerFunction a Source #
Arguments
| = Vector Double | Parameter vector |
| -> Vector Double | Vector |
| -> IOVector Double | Output vector |
| -> a | User data |
| -> IO () |
This function type corresponds to nlopt_precond in C and is
used for functions that precondition a vector at a given point in
the parameter space. You may pass data of any type a to the
functions in this module that take a PreconditionerFunction as an
argument; this data will be supplied to your function when it is
called.
Running the optimizer
The output of an NLOPT optimizer run.
Constructors
| Output | |
Fields
| |
Arguments
| :: Opt | Optimizer object set up to solve the problem |
| -> Vector Double | Initial-guess parameter vector |
| -> IO Output | Results of the optimization run |
This function is very similar to the C function nlopt_optimize,
but it does not use mutable vectors and returns an Output
structure.
Objective function configuration
set_min_objective :: Opt -> ScalarFunction a -> a -> IO Result Source #
set_max_objective :: Opt -> ScalarFunction a -> a -> IO Result Source #
set_precond_min_objective :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> IO Result Source #
set_precond_max_objective :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> IO Result Source #
Bound configuration
Constraint configuration
add_inequality_constraint :: Opt -> ScalarFunction a -> a -> Double -> IO Result Source #
add_precond_inequality_constraint :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> Double -> IO Result Source #
add_inequality_mconstraint :: Opt -> Word -> VectorFunction a -> a -> Double -> IO Result Source #
add_equality_constraint :: Opt -> ScalarFunction a -> a -> Double -> IO Result Source #
add_precond_equality_constraint :: Opt -> ScalarFunction a -> PreconditionerFunction a -> a -> Double -> IO Result Source #
add_equality_mconstraint :: Opt -> Word -> VectorFunction a -> a -> Double -> IO Result Source #