{-# OPTIONS_GHC -Wall #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Core.Data where import Prelude hiding ( Functor ) import Foreign.Ptr ( Ptr, FunPtr ) import Foreign.ForeignPtr ( ForeignPtr, castForeignPtr, newForeignPtr, touchForeignPtr ) import Foreign.ForeignPtr.Unsafe ( unsafeForeignPtrToPtr ) import Casadi.Internal.Marshal ( Marshal(..) ) import Casadi.Internal.WrapReturn ( WrapReturn(..) ) -- raw decl data Callback' -- data decl {-| >Callback. > >In C++, supply a CallbackCPtr function pointer When the callback function >returns a non-zero integer, the host is signalled of a problem. E.g. an >NlpSolver may halt iterations if the Callback is something else than 0 > >In python, supply a callable, annotated with pycallback decorator > >C++ includes: functor.hpp -} newtype Callback = Callback (ForeignPtr Callback') -- typeclass decl class CallbackClass a where castCallback :: a -> Callback instance CallbackClass Callback where castCallback = id -- baseclass instances instance FunctorClass Callback where castFunctor (Callback x) = Functor (castForeignPtr x) instance PrintableObjectClass Callback where castPrintableObject (Callback x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Callback where castSharedObject (Callback x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal Callback (Ptr Callback') where marshal (Callback x) = return (unsafeForeignPtrToPtr x) marshalFree (Callback x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Callback" c_delete_casadi__Callback :: FunPtr (Ptr Callback' -> IO ()) instance WrapReturn (Ptr Callback') Callback where wrapReturn = (fmap Callback) . (newForeignPtr c_delete_casadi__Callback) -- raw decl data CasadiMeta' -- data decl {-| >Collects global CasADi meta information. > >Joris Gillis > >C++ includes: casadi_meta.hpp -} newtype CasadiMeta = CasadiMeta (ForeignPtr CasadiMeta') -- typeclass decl class CasadiMetaClass a where castCasadiMeta :: a -> CasadiMeta instance CasadiMetaClass CasadiMeta where castCasadiMeta = id -- baseclass instances -- helper instances instance Marshal CasadiMeta (Ptr CasadiMeta') where marshal (CasadiMeta x) = return (unsafeForeignPtrToPtr x) marshalFree (CasadiMeta x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__CasadiMeta" c_delete_casadi__CasadiMeta :: FunPtr (Ptr CasadiMeta' -> IO ()) instance WrapReturn (Ptr CasadiMeta') CasadiMeta where wrapReturn = (fmap CasadiMeta) . (newForeignPtr c_delete_casadi__CasadiMeta) -- raw decl data CasadiOptions' -- data decl {-| >Collects global CasADi options. > >Note to developers: use sparingly. Global options are - in general - a >rather bad idea > >this class must never be instantiated. Access its static members directly >Joris Gillis > >C++ includes: casadi_options.hpp -} newtype CasadiOptions = CasadiOptions (ForeignPtr CasadiOptions') -- typeclass decl class CasadiOptionsClass a where castCasadiOptions :: a -> CasadiOptions instance CasadiOptionsClass CasadiOptions where castCasadiOptions = id -- baseclass instances -- helper instances instance Marshal CasadiOptions (Ptr CasadiOptions') where marshal (CasadiOptions x) = return (unsafeForeignPtrToPtr x) marshalFree (CasadiOptions x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__CasadiOptions" c_delete_casadi__CasadiOptions :: FunPtr (Ptr CasadiOptions' -> IO ()) instance WrapReturn (Ptr CasadiOptions') CasadiOptions where wrapReturn = (fmap CasadiOptions) . (newForeignPtr c_delete_casadi__CasadiOptions) -- raw decl data ControlSimulator' -- data decl {-| >Piecewise Simulation class. > >A ControlSimulator can be seen as a chain of Simulators whereby some >parameters change from one Simulator to the next. > >These changing parameters can typically be interpreted as "controls" in >the context of dynamic optimization. > >We discriminate between the following time steps: Major time-steps. These >are the time steps provided by the supplied grid. Controls are constant >inbetween major time-steps Minor time-steps. These are time steps linearly >interpolated from one major time-step to the next. The option 'nf' regulates >how many minor time-steps are taken. Integration time-steps. Time steps >that the supplied integrator might choose to integrate the continuous >dynamics. They are not important what ControlSimulator is concerned. np >Number of parameters nu Number of controls ns The number of major grid >points, as supplied in the constructor nf The number of minor grid points >per major interval > >Joris Gillis > >>Input scheme: casadi::ControlSimulatorInput (CONTROLSIMULATOR_NUM_IN = 3) [controlsimulatorIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| CONTROLSIMULATOR_X0 | x0 | Differential or | >| | | algebraic state at t0 | >| | | (dimension nx-by-1) . | >+------------------------+------------------------+------------------------+ >| CONTROLSIMULATOR_P | p | Parameters that are | >| | | fixed over the entire | >| | | horizon (dimension np- | >| | | by-1) . | >+------------------------+------------------------+------------------------+ >| CONTROLSIMULATOR_U | u | Parameters that change | >| | | over the integration | >| | | intervals (dimension | >| | | nu-by-(ns-1)) . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| control_endp | OT_BOOLEAN | false | Include a | casadi::Cont | >| oint | | | control | rolSimulator | >| | | | value at the | Internal | >| | | | end of the | | >| | | | simulation | | >| | | | domain. Used | | >| | | | for interpol | | >| | | | ation. | | >+--------------+--------------+--------------+--------------+--------------+ >| control_inte | OT_STRING | "none" | none|nearest | casadi::Cont | >| rpolation | | | |linear | rolSimulator | >| | | | | Internal | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| integrator | OT_STRING | GenericType( | An | casadi::Cont | >| | | ) | integrator | rolSimulator | >| | | | creator | Internal | >| | | | function | | >+--------------+--------------+--------------+--------------+--------------+ >| integrator_o | OT_DICTIONAR | GenericType( | Options to | casadi::Cont | >| ptions | Y | ) | be passed to | rolSimulator | >| | | | the | Internal | >| | | | integrator | | >+--------------+--------------+--------------+--------------+--------------+ >| minor_grid | OT_INTEGERVE | GenericType( | The local | casadi::Cont | >| | CTOR | ) | grid used on | rolSimulator | >| | | | each major | Internal | >| | | | interval, | | >| | | | with time | | >| | | | normalized | | >| | | | to 1. By | | >| | | | default, | | >| | | | option 'nf' | | >| | | | is used to | | >| | | | construct a | | >| | | | linearly | | >| | | | spaced grid. | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| nf | OT_INTEGER | 1 | Number of | casadi::Cont | >| | | | minor | rolSimulator | >| | | | grained | Internal | >| | | | integration | | >| | | | steps per | | >| | | | major | | >| | | | interval. | | >| | | | nf>0 must | | >| | | | hold. This | | >| | | | option is | | >| | | | not used | | >| | | | when | | >| | | | 'minor_grid' | | >| | | | is provided. | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| simulator_op | OT_DICTIONAR | GenericType( | Options to | casadi::Cont | >| tions | Y | ) | be passed to | rolSimulator | >| | | | the | Internal | >| | | | simulator | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: control_simulator.hpp -} newtype ControlSimulator = ControlSimulator (ForeignPtr ControlSimulator') -- typeclass decl class ControlSimulatorClass a where castControlSimulator :: a -> ControlSimulator instance ControlSimulatorClass ControlSimulator where castControlSimulator = id -- baseclass instances instance FunctionClass ControlSimulator where castFunction (ControlSimulator x) = Function (castForeignPtr x) instance OptionsFunctionalityClass ControlSimulator where castOptionsFunctionality (ControlSimulator x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass ControlSimulator where castPrintableObject (ControlSimulator x) = PrintableObject (castForeignPtr x) instance SharedObjectClass ControlSimulator where castSharedObject (ControlSimulator x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass ControlSimulator where castIOInterfaceFunction (ControlSimulator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal ControlSimulator (Ptr ControlSimulator') where marshal (ControlSimulator x) = return (unsafeForeignPtrToPtr x) marshalFree (ControlSimulator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__ControlSimulator" c_delete_casadi__ControlSimulator :: FunPtr (Ptr ControlSimulator' -> IO ()) instance WrapReturn (Ptr ControlSimulator') ControlSimulator where wrapReturn = (fmap ControlSimulator) . (newForeignPtr c_delete_casadi__ControlSimulator) -- raw decl data CustomEvaluate' -- data decl {-| >CustomEvaluate. > >In C++, supply a CustomEvaluateCPtr function pointer > >In python, supply a callable, annotated with pyevaluate decorator > >C++ includes: functor.hpp -} newtype CustomEvaluate = CustomEvaluate (ForeignPtr CustomEvaluate') -- typeclass decl class CustomEvaluateClass a where castCustomEvaluate :: a -> CustomEvaluate instance CustomEvaluateClass CustomEvaluate where castCustomEvaluate = id -- baseclass instances instance FunctorClass CustomEvaluate where castFunctor (CustomEvaluate x) = Functor (castForeignPtr x) instance PrintableObjectClass CustomEvaluate where castPrintableObject (CustomEvaluate x) = PrintableObject (castForeignPtr x) instance SharedObjectClass CustomEvaluate where castSharedObject (CustomEvaluate x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal CustomEvaluate (Ptr CustomEvaluate') where marshal (CustomEvaluate x) = return (unsafeForeignPtrToPtr x) marshalFree (CustomEvaluate x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__CustomEvaluate" c_delete_casadi__CustomEvaluate :: FunPtr (Ptr CustomEvaluate' -> IO ()) instance WrapReturn (Ptr CustomEvaluate') CustomEvaluate where wrapReturn = (fmap CustomEvaluate) . (newForeignPtr c_delete_casadi__CustomEvaluate) -- raw decl data CustomFunction' -- data decl {-| >Interface to a custom function. > >Joel Andersson > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: custom_function.hpp -} newtype CustomFunction = CustomFunction (ForeignPtr CustomFunction') -- typeclass decl class CustomFunctionClass a where castCustomFunction :: a -> CustomFunction instance CustomFunctionClass CustomFunction where castCustomFunction = id -- baseclass instances instance FunctionClass CustomFunction where castFunction (CustomFunction x) = Function (castForeignPtr x) instance OptionsFunctionalityClass CustomFunction where castOptionsFunctionality (CustomFunction x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass CustomFunction where castPrintableObject (CustomFunction x) = PrintableObject (castForeignPtr x) instance SharedObjectClass CustomFunction where castSharedObject (CustomFunction x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass CustomFunction where castIOInterfaceFunction (CustomFunction x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal CustomFunction (Ptr CustomFunction') where marshal (CustomFunction x) = return (unsafeForeignPtrToPtr x) marshalFree (CustomFunction x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__CustomFunction" c_delete_casadi__CustomFunction :: FunPtr (Ptr CustomFunction' -> IO ()) instance WrapReturn (Ptr CustomFunction') CustomFunction where wrapReturn = (fmap CustomFunction) . (newForeignPtr c_delete_casadi__CustomFunction) -- raw decl data DMatrix' -- data decl {-| -} newtype DMatrix = DMatrix (ForeignPtr DMatrix') -- typeclass decl class DMatrixClass a where castDMatrix :: a -> DMatrix instance DMatrixClass DMatrix where castDMatrix = id -- baseclass instances instance PrintableObjectClass DMatrix where castPrintableObject (DMatrix x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal DMatrix (Ptr DMatrix') where marshal (DMatrix x) = return (unsafeForeignPtrToPtr x) marshalFree (DMatrix x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__DMatrix" c_delete_casadi__DMatrix :: FunPtr (Ptr DMatrix' -> IO ()) instance WrapReturn (Ptr DMatrix') DMatrix where wrapReturn = (fmap DMatrix) . (newForeignPtr c_delete_casadi__DMatrix) -- raw decl data DerivativeGenerator' -- data decl {-| >Derivative Generator Functor. > >In C++, supply a DerivativeGeneratorCPtr function pointer > >In python, supply a callable, annotated with derivativegenerator decorator > >C++ includes: functor.hpp -} newtype DerivativeGenerator = DerivativeGenerator (ForeignPtr DerivativeGenerator') -- typeclass decl class DerivativeGeneratorClass a where castDerivativeGenerator :: a -> DerivativeGenerator instance DerivativeGeneratorClass DerivativeGenerator where castDerivativeGenerator = id -- baseclass instances instance FunctorClass DerivativeGenerator where castFunctor (DerivativeGenerator x) = Functor (castForeignPtr x) instance PrintableObjectClass DerivativeGenerator where castPrintableObject (DerivativeGenerator x) = PrintableObject (castForeignPtr x) instance SharedObjectClass DerivativeGenerator where castSharedObject (DerivativeGenerator x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal DerivativeGenerator (Ptr DerivativeGenerator') where marshal (DerivativeGenerator x) = return (unsafeForeignPtrToPtr x) marshalFree (DerivativeGenerator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__DerivativeGenerator" c_delete_casadi__DerivativeGenerator :: FunPtr (Ptr DerivativeGenerator' -> IO ()) instance WrapReturn (Ptr DerivativeGenerator') DerivativeGenerator where wrapReturn = (fmap DerivativeGenerator) . (newForeignPtr c_delete_casadi__DerivativeGenerator) -- raw decl data ExternalFunction' -- data decl {-| >Interface for a function that is not implemented by CasADi symbolics. > >Joel Andersson > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: external_function.hpp -} newtype ExternalFunction = ExternalFunction (ForeignPtr ExternalFunction') -- typeclass decl class ExternalFunctionClass a where castExternalFunction :: a -> ExternalFunction instance ExternalFunctionClass ExternalFunction where castExternalFunction = id -- baseclass instances instance FunctionClass ExternalFunction where castFunction (ExternalFunction x) = Function (castForeignPtr x) instance OptionsFunctionalityClass ExternalFunction where castOptionsFunctionality (ExternalFunction x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass ExternalFunction where castPrintableObject (ExternalFunction x) = PrintableObject (castForeignPtr x) instance SharedObjectClass ExternalFunction where castSharedObject (ExternalFunction x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass ExternalFunction where castIOInterfaceFunction (ExternalFunction x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal ExternalFunction (Ptr ExternalFunction') where marshal (ExternalFunction x) = return (unsafeForeignPtrToPtr x) marshalFree (ExternalFunction x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__ExternalFunction" c_delete_casadi__ExternalFunction :: FunPtr (Ptr ExternalFunction' -> IO ()) instance WrapReturn (Ptr ExternalFunction') ExternalFunction where wrapReturn = (fmap ExternalFunction) . (newForeignPtr c_delete_casadi__ExternalFunction) -- raw decl data Function' -- data decl {-| >General function. > >A general function $f$ in casadi can be multi-input, multi-output. Number of >inputs: nin getNumInputs() Number of outputs: nout getNumOutputs() We can >view this function as a being composed of a ( nin, nout) grid of single- >input, single-output primitive functions. Each such primitive function $f_ >{i, j} \\\\forall i \\\\in [0, nin-1], j \\\\in [0, nout-1]$ can map as >$\\\\mathbf {R}^{n, m}\\\\to\\\\mathbf{R}^{p, q}$, in which n, m, p, q can >take different values for every (i, j) pair. When passing input, you >specify which partition $i$ is active. You pass the numbers vectorized, as a >vector of size $(n*m)$. When requesting output, you specify which partition >$j$ is active. You get the numbers vectorized, as a vector of size $(p*q)$. >To calculate Jacobians, you need to have $(m=1, q=1)$. > >Write the Jacobian as $J_ {i, j} = \\\\nabla f_{i, j} = \\\\frac >{\\\\partial f_{i, j}(\\\\vec{x})}{\\\\partial \\\\vec{x}}$. > >Using $\\\\vec {v} \\\\in \\\\mathbf{R}^n$ as a forward seed: setFwdSeed(v, >i) Retrieving $\\\\vec {s}_f \\\\in \\\\mathbf{R}^p$ from: getFwdSens(sf, j) >Using $\\\\vec {w} \\\\in \\\\mathbf{R}^p$ as a forward seed: setAdjSeed(w, >j) Retrieving $\\\\vec {s}_a \\\\in \\\\mathbf{R}^n $ from: getAdjSens(sa, >i) We have the following relationships for function mapping from a row >vector to a row vector: > >$ \\\\vec {s}_f = \\\\nabla f_{i, j} . \\\\vec{v}$ $ \\\\vec {s}_a = >(\\\\nabla f_{i, j})^T . \\\\vec{w}$ > >Some quantities in these formulas must be transposed: input col: transpose $ >\\\\vec {v} $ and $\\\\vec{s}_a$ output col: transpose $ \\\\vec {w} $ and >$\\\\vec{s}_f$ NOTE: Functions are allowed to modify their input arguments >when evaluating: implicitFunction, IDAS solver Further releases may disallow >this. > >Joel Andersson > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available monitors > >+---------+--------------------------+ >| Id | Used in | >+=========+==========================+ >| inputs | casadi::FunctionInternal | >+---------+--------------------------+ >| outputs | casadi::FunctionInternal | >+---------+--------------------------+ > >Diagrams >-------- > > > >C++ includes: function.hpp -} newtype Function = Function (ForeignPtr Function') -- typeclass decl class FunctionClass a where castFunction :: a -> Function instance FunctionClass Function where castFunction = id -- baseclass instances instance OptionsFunctionalityClass Function where castOptionsFunctionality (Function x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass Function where castPrintableObject (Function x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Function where castSharedObject (Function x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass Function where castIOInterfaceFunction (Function x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal Function (Ptr Function') where marshal (Function x) = return (unsafeForeignPtrToPtr x) marshalFree (Function x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Function" c_delete_casadi__Function :: FunPtr (Ptr Function' -> IO ()) instance WrapReturn (Ptr Function') Function where wrapReturn = (fmap Function) . (newForeignPtr c_delete_casadi__Function) -- raw decl data Functor' -- data decl {-| >Functor. > >Joris Gillis > >C++ includes: functor.hpp -} newtype Functor = Functor (ForeignPtr Functor') -- typeclass decl class FunctorClass a where castFunctor :: a -> Functor instance FunctorClass Functor where castFunctor = id -- baseclass instances instance PrintableObjectClass Functor where castPrintableObject (Functor x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Functor where castSharedObject (Functor x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal Functor (Ptr Functor') where marshal (Functor x) = return (unsafeForeignPtrToPtr x) marshalFree (Functor x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Functor" c_delete_casadi__Functor :: FunPtr (Ptr Functor' -> IO ()) instance WrapReturn (Ptr Functor') Functor where wrapReturn = (fmap Functor) . (newForeignPtr c_delete_casadi__Functor) -- raw decl data GenericType' -- data decl {-| >Generic data type. > >Joel Andersson > >C++ includes: generic_type.hpp -} newtype GenericType = GenericType (ForeignPtr GenericType') -- typeclass decl class GenericTypeClass a where castGenericType :: a -> GenericType instance GenericTypeClass GenericType where castGenericType = id -- baseclass instances instance PrintableObjectClass GenericType where castPrintableObject (GenericType x) = PrintableObject (castForeignPtr x) instance SharedObjectClass GenericType where castSharedObject (GenericType x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal GenericType (Ptr GenericType') where marshal (GenericType x) = return (unsafeForeignPtrToPtr x) marshalFree (GenericType x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__GenericType" c_delete_casadi__GenericType :: FunPtr (Ptr GenericType' -> IO ()) instance WrapReturn (Ptr GenericType') GenericType where wrapReturn = (fmap GenericType) . (newForeignPtr c_delete_casadi__GenericType) -- raw decl data HomotopyNlpSolver' -- data decl {-| >Base class for Homotopy NLP Solvers. > >Solves the following parametric nonlinear program (NLP): > >:: > > min F(x, p, tau) > x > > subject to > LBX <= x <= UBX > LBG <= G(x, p) <= UBG > p == P > > nx: number of decision variables > ng: number of constraints > np: number of parameters > > > > >In a homotopy from tau = 0 to tau = 1. > >General information >=================== > > > >>Input scheme: casadi::NlpSolverInput (NLP_SOLVER_NUM_IN = 8) [nlpSolverIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| NLP_SOLVER_X0 | x0 | Decision variables, | >| | | initial guess (nx x 1) | >| | | . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_P | p | Value of fixed | >| | | parameters (np x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LBX | lbx | Decision variables | >| | | lower bound (nx x 1), | >| | | default -inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_UBX | ubx | Decision variables | >| | | upper bound (nx x 1), | >| | | default +inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LBG | lbg | Constraints lower | >| | | bound (ng x 1), | >| | | default -inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_UBG | ubg | Constraints upper | >| | | bound (ng x 1), | >| | | default +inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_X0 | lam_x0 | Lagrange multipliers | >| | | for bounds on X, | >| | | initial guess (nx x 1) | >| | | . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_G0 | lam_g0 | Lagrange multipliers | >| | | for bounds on G, | >| | | initial guess (ng x 1) | >| | | . | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::NlpSolverOutput (NLP_SOLVER_NUM_OUT = 6) [nlpSolverOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| NLP_SOLVER_X | x | Decision variables at | >| | | the optimal solution | >| | | (nx x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_F | f | Cost function value at | >| | | the optimal solution | >| | | (1 x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_G | g | Constraints function | >| | | at the optimal | >| | | solution (ng x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_X | lam_x | Lagrange multipliers | >| | | for bounds on X at the | >| | | solution (nx x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_G | lam_g | Lagrange multipliers | >| | | for bounds on G at the | >| | | solution (ng x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_P | lam_p | Lagrange multipliers | >| | | for bounds on P at the | >| | | solution (np x 1) . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| expand | OT_BOOLEAN | false | Expand the | casadi::Homo | >| | | | NLP function | topyNLPInter | >| | | | in terms of | nal | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- simple > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >HomotopyNlpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >simple >------ > > > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| nlp_solver | OT_STRING | GenericType() | The NLP solver | >| | | | to be used by | >| | | | the Homotopy | >| | | | solver | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_solver_opti | OT_DICTIONARY | GenericType() | Options to be | >| ons | | | passed to the | >| | | | Homotopy solver | >+-----------------+-----------------+-----------------+-----------------+ >| num_steps | OT_INTEGER | 10 | Take this many | >| | | | steps to go | >| | | | from tau=0 to | >| | | | tau=1. | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >Joris Gillis >Diagrams >-------- > > > >C++ includes: homotopy_nlp_solver.hpp -} newtype HomotopyNlpSolver = HomotopyNlpSolver (ForeignPtr HomotopyNlpSolver') -- typeclass decl class HomotopyNlpSolverClass a where castHomotopyNlpSolver :: a -> HomotopyNlpSolver instance HomotopyNlpSolverClass HomotopyNlpSolver where castHomotopyNlpSolver = id -- baseclass instances instance FunctionClass HomotopyNlpSolver where castFunction (HomotopyNlpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass HomotopyNlpSolver where castOptionsFunctionality (HomotopyNlpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass HomotopyNlpSolver where castPrintableObject (HomotopyNlpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass HomotopyNlpSolver where castSharedObject (HomotopyNlpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass HomotopyNlpSolver where castIOInterfaceFunction (HomotopyNlpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal HomotopyNlpSolver (Ptr HomotopyNlpSolver') where marshal (HomotopyNlpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (HomotopyNlpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__HomotopyNlpSolver" c_delete_casadi__HomotopyNlpSolver :: FunPtr (Ptr HomotopyNlpSolver' -> IO ()) instance WrapReturn (Ptr HomotopyNlpSolver') HomotopyNlpSolver where wrapReturn = (fmap HomotopyNlpSolver) . (newForeignPtr c_delete_casadi__HomotopyNlpSolver) -- raw decl data IMatrix' -- data decl {-| -} newtype IMatrix = IMatrix (ForeignPtr IMatrix') -- typeclass decl class IMatrixClass a where castIMatrix :: a -> IMatrix instance IMatrixClass IMatrix where castIMatrix = id -- baseclass instances instance PrintableObjectClass IMatrix where castPrintableObject (IMatrix x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal IMatrix (Ptr IMatrix') where marshal (IMatrix x) = return (unsafeForeignPtrToPtr x) marshalFree (IMatrix x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__IMatrix" c_delete_casadi__IMatrix :: FunPtr (Ptr IMatrix' -> IO ()) instance WrapReturn (Ptr IMatrix') IMatrix where wrapReturn = (fmap IMatrix) . (newForeignPtr c_delete_casadi__IMatrix) -- raw decl data IOScheme' -- data decl {-| >Class with mapping between names and indices. > >Joris Gillis > >C++ includes: io_scheme.hpp -} newtype IOScheme = IOScheme (ForeignPtr IOScheme') -- typeclass decl class IOSchemeClass a where castIOScheme :: a -> IOScheme instance IOSchemeClass IOScheme where castIOScheme = id -- baseclass instances instance PrintableObjectClass IOScheme where castPrintableObject (IOScheme x) = PrintableObject (castForeignPtr x) instance SharedObjectClass IOScheme where castSharedObject (IOScheme x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal IOScheme (Ptr IOScheme') where marshal (IOScheme x) = return (unsafeForeignPtrToPtr x) marshalFree (IOScheme x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__IOScheme" c_delete_casadi__IOScheme :: FunPtr (Ptr IOScheme' -> IO ()) instance WrapReturn (Ptr IOScheme') IOScheme where wrapReturn = (fmap IOScheme) . (newForeignPtr c_delete_casadi__IOScheme) -- raw decl data ImplicitFunction' -- data decl {-| >Abstract base class for the implicit function classes. > >The equation: > >F(z, x1, x2, ..., xn) == 0 > >where d_F/dz is invertible, implicitly defines the equation: > >z := G(x1, x2, ..., xn) > >F should be an Function mapping from (n+1) inputs to m outputs. The first >output is the residual that should be zero. > >ImplicitFunction (G) is an Function mapping from n inputs to m outputs. n >may be zero. The first output is the solved for z. > >You can provide an initial guess for z by setting output(0) of >ImplicitFunction. > >General information >=================== > > > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| constraints | OT_INTEGERVE | GenericType( | Constrain | casadi::Impl | >| | CTOR | ) | the | icitFunction | >| | | | unknowns. 0 | Internal | >| | | | (default): | | >| | | | no | | >| | | | constraint | | >| | | | on ui, 1: ui | | >| | | | >= 0.0, -1: | | >| | | | ui <= 0.0, | | >| | | | 2: ui > 0.0, | | >| | | | -2: ui < | | >| | | | 0.0. | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_inp | OT_INTEGER | 0 | Index of the | casadi::Impl | >| ut | | | input that | icitFunction | >| | | | corresponds | Internal | >| | | | to the | | >| | | | actual root- | | >| | | | finding | | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_out | OT_INTEGER | 0 | Index of the | casadi::Impl | >| put | | | output that | icitFunction | >| | | | corresponds | Internal | >| | | | to the | | >| | | | actual root- | | >| | | | finding | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | GenericType( | User-defined | casadi::Impl | >| r | | ) | linear | icitFunction | >| | | | solver | Internal | >| | | | class. | | >| | | | Needed for s | | >| | | | ensitivities | | >| | | | . | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | casadi::Impl | >| r_options | Y | ) | be passed to | icitFunction | >| | | | the linear | Internal | >| | | | solver. | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- kinsol > >- newton > >- nlp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >ImplicitFunction.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >kinsol >------ > > > >KINSOL interface from the Sundials suite > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| abstol | OT_REAL | 0.000 | Stopping | >| | | | criterion | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| disable_interna | OT_BOOLEAN | false | Disable KINSOL | >| l_warnings | | | internal | >| | | | warning | >| | | | messages | >+-----------------+-----------------+-----------------+-----------------+ >| exact_jacobian | OT_BOOLEAN | true | | >+-----------------+-----------------+-----------------+-----------------+ >| f_scale | OT_REALVECTOR | | | >+-----------------+-----------------+-----------------+-----------------+ >| iterative_solve | OT_STRING | "gmres" | gmres|bcgstab|t | >| r | | | fqmr | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_t | OT_STRING | "dense" | dense|banded|it | >| ype | | | erative|user_de | >| | | | fined | >+-----------------+-----------------+-----------------+-----------------+ >| lower_bandwidth | OT_INTEGER | | | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter | OT_INTEGER | 0 | Maximum number | >| | | | of Newton | >| | | | iterations. | >| | | | Putting 0 sets | >| | | | the default | >| | | | value of | >| | | | KinSol. | >+-----------------+-----------------+-----------------+-----------------+ >| max_krylov | OT_INTEGER | 0 | | >+-----------------+-----------------+-----------------+-----------------+ >| pretype | OT_STRING | "none" | (none|left|righ | >| | | | t|both) | >+-----------------+-----------------+-----------------+-----------------+ >| strategy | OT_STRING | "none" | Globalization | >| | | | strategy (none| | >| | | | linesearch) | >+-----------------+-----------------+-----------------+-----------------+ >| u_scale | OT_REALVECTOR | | | >+-----------------+-----------------+-----------------+-----------------+ >| upper_bandwidth | OT_INTEGER | | | >+-----------------+-----------------+-----------------+-----------------+ >| use_preconditio | OT_BOOLEAN | false | precondition an | >| ner | | | iterative | >| | | | solver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-----------+ >| Id | >+===========+ >| eval_djac | >+-----------+ >| eval_f | >+-----------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >newton >------ > > > >Implements simple newton iterations to solve an implicit function. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| abstol | OT_REAL | 0.000 | Stopping | >| | | | criterion | >| | | | tolerance on | >| | | | max(|F|) | >+-----------------+-----------------+-----------------+-----------------+ >| abstolStep | OT_REAL | 0.000 | Stopping | >| | | | criterion | >| | | | tolerance on | >| | | | step size | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter | OT_INTEGER | 1000 | Maximum number | >| | | | of Newton | >| | | | iterations to | >| | | | perform before | >| | | | returning. | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+----------+ >| Id | >+==========+ >| F | >+----------+ >| J | >+----------+ >| normF | >+----------+ >| step | >+----------+ >| stepsize | >+----------+ > >>List of available stats > >+---------------+ >| Id | >+===============+ >| iter | >+---------------+ >| return_status | >+---------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >nlp >--- > > > >Use an NlpSolver as ImplicitFunction solver > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| nlp_solver | OT_STRING | GenericType() | The NlpSolver | >| | | | used to solve | >| | | | the implicit | >| | | | system. | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_solver_opti | OT_DICTIONARY | GenericType() | Options to be | >| ons | | | passed to the | >| | | | NlpSolver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+------------------+ >| Id | >+==================+ >| nlp_solver_stats | >+------------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: implicit_function.hpp -} newtype ImplicitFunction = ImplicitFunction (ForeignPtr ImplicitFunction') -- typeclass decl class ImplicitFunctionClass a where castImplicitFunction :: a -> ImplicitFunction instance ImplicitFunctionClass ImplicitFunction where castImplicitFunction = id -- baseclass instances instance FunctionClass ImplicitFunction where castFunction (ImplicitFunction x) = Function (castForeignPtr x) instance OptionsFunctionalityClass ImplicitFunction where castOptionsFunctionality (ImplicitFunction x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass ImplicitFunction where castPrintableObject (ImplicitFunction x) = PrintableObject (castForeignPtr x) instance SharedObjectClass ImplicitFunction where castSharedObject (ImplicitFunction x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass ImplicitFunction where castIOInterfaceFunction (ImplicitFunction x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal ImplicitFunction (Ptr ImplicitFunction') where marshal (ImplicitFunction x) = return (unsafeForeignPtrToPtr x) marshalFree (ImplicitFunction x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__ImplicitFunction" c_delete_casadi__ImplicitFunction :: FunPtr (Ptr ImplicitFunction' -> IO ()) instance WrapReturn (Ptr ImplicitFunction') ImplicitFunction where wrapReturn = (fmap ImplicitFunction) . (newForeignPtr c_delete_casadi__ImplicitFunction) -- raw decl data Integrator' -- data decl {-| >Base class for integrators. > >Integrator abstract base class > >Solves an initial value problem (IVP) coupled to a terminal value problem >with differential equation given as an implicit ODE coupled to an algebraic >equation and a set of quadratures: > >:: > > Initial conditions at t=t0 > x(t0) = x0 > q(t0) = 0 > > Forward integration from t=t0 to t=tf > der(x) = function(x, z, p, t) Forward ODE > 0 = fz(x, z, p, t) Forward algebraic equations > der(q) = fq(x, z, p, t) Forward quadratures > > Terminal conditions at t=tf > rx(tf) = rx0 > rq(tf) = 0 > > Backward integration from t=tf to t=t0 > der(rx) = gx(rx, rz, rp, x, z, p, t) Backward ODE > 0 = gz(rx, rz, rp, x, z, p, t) Backward algebraic equations > der(rq) = gq(rx, rz, rp, x, z, p, t) Backward quadratures > > where we assume that both the forward and backwards integrations are index-1 > (i.e. dfz/dz, dgz/drz are invertible) and furthermore that > gx, gz and gq have a linear dependency on rx, rz and rp. > > > >The Integrator class provides some additional functionality, such as getting >the value of the state and/or sensitivities at certain time points. > >General information >=================== > > > >>Input scheme: casadi::IntegratorInput (INTEGRATOR_NUM_IN = 6) [integratorIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| INTEGRATOR_X0 | x0 | Differential state at | >| | | the initial time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_P | p | Parameters . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_Z0 | z0 | Initial guess for the | >| | | algebraic variable . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RX0 | rx0 | Backward differential | >| | | state at the final | >| | | time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RP | rp | Backward parameter | >| | | vector . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RZ0 | rz0 | Initial guess for the | >| | | backwards algebraic | >| | | variable . | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::IntegratorOutput (INTEGRATOR_NUM_OUT = 6) [integratorOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| INTEGRATOR_XF | xf | Differential state at | >| | | the final time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_QF | qf | Quadrature state at | >| | | the final time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_ZF | zf | Algebraic variable at | >| | | the final time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RXF | rxf | Backward differential | >| | | state at the initial | >| | | time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RQF | rqf | Backward quadrature | >| | | state at the initial | >| | | time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RZF | rzf | Backward algebraic | >| | | variable at the | >| | | initial time . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| augmented_op | OT_DICTIONAR | GenericType( | Options to | casadi::Inte | >| tions | Y | ) | be passed | gratorIntern | >| | | | down to the | al | >| | | | augmented | | >| | | | integrator, | | >| | | | if one is | | >| | | | constructed. | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_augme | OT_BOOLEAN | true | If DAE | casadi::Inte | >| nted | | | callback | gratorIntern | >| | | | functions | al | >| | | | are | | >| | | | SXFunction , | | >| | | | have | | >| | | | augmented | | >| | | | DAE callback | | >| | | | function | | >| | | | also be | | >| | | | SXFunction . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| print_stats | OT_BOOLEAN | false | Print out | casadi::Inte | >| | | | statistics | gratorIntern | >| | | | after | al | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| t0 | OT_REAL | 0 | Beginning of | casadi::Inte | >| | | | the time | gratorIntern | >| | | | horizon | al | >+--------------+--------------+--------------+--------------+--------------+ >| tf | OT_REAL | 1 | End of the | casadi::Inte | >| | | | time horizon | gratorIntern | >| | | | | al | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- cvodes > >- idas > >- collocation > >- oldcollocation > >- rk > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >Integrator.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >cvodes >------ > > > >Interface to CVodes from the Sundials suite. > >A call to evaluate will integrate to the end. > >You can retrieve the entire state trajectory as follows, after the evaluate >call: Call reset. Then call integrate(t_i) and getOuput for a series of >times t_i. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| abstol | OT_REAL | 0.000 | Absolute | >| | | | tolerence for | >| | | | the IVP | >| | | | solution | >+-----------------+-----------------+-----------------+-----------------+ >| abstolB | OT_REAL | GenericType() | Absolute | >| | | | tolerence for | >| | | | the adjoint | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to abstol] | >+-----------------+-----------------+-----------------+-----------------+ >| disable_interna | OT_BOOLEAN | false | Disable CVodes | >| l_warnings | | | internal | >| | | | warning | >| | | | messages | >+-----------------+-----------------+-----------------+-----------------+ >| exact_jacobian | OT_BOOLEAN | true | Use exact | >| | | | Jacobian | >| | | | information for | >| | | | the forward | >| | | | integration | >+-----------------+-----------------+-----------------+-----------------+ >| exact_jacobianB | OT_BOOLEAN | GenericType() | Use exact | >| | | | Jacobian | >| | | | information for | >| | | | the backward | >| | | | integration | >| | | | [default: equal | >| | | | to | >| | | | exact_jacobian] | >+-----------------+-----------------+-----------------+-----------------+ >| finite_differen | OT_BOOLEAN | false | Use finite | >| ce_fsens | | | differences to | >| | | | approximate the | >| | | | forward | >| | | | sensitivity | >| | | | equations (if | >| | | | AD is not | >| | | | available) | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_abstol | OT_REAL | GenericType() | Absolute | >| | | | tolerence for | >| | | | the forward | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to abstol] | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_all_at_on | OT_BOOLEAN | true | Calculate all | >| ce | | | right hand | >| | | | sides of the | >| | | | sensitivity | >| | | | equations at | >| | | | once | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_err_con | OT_BOOLEAN | true | include the | >| | | | forward | >| | | | sensitivities | >| | | | in all error | >| | | | controls | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_reltol | OT_REAL | GenericType() | Relative | >| | | | tolerence for | >| | | | the forward | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to reltol] | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_scaling_f | OT_REALVECTOR | GenericType() | Scaling factor | >| actors | | | for the | >| | | | components if | >| | | | finite | >| | | | differences is | >| | | | used | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_sensitivi | OT_INTEGERVECTO | GenericType() | Specifies which | >| y_parameters | R | | components will | >| | | | be used when | >| | | | estimating the | >| | | | sensitivity | >| | | | equations | >+-----------------+-----------------+-----------------+-----------------+ >| interpolation_t | OT_STRING | "hermite" | Type of | >| ype | | | interpolation | >| | | | for the adjoint | >| | | | sensitivities ( | >| | | | hermite|polynom | >| | | | ial) | >+-----------------+-----------------+-----------------+-----------------+ >| iterative_solve | OT_STRING | "gmres" | (gmres|bcgstab| | >| r | | | tfqmr) | >+-----------------+-----------------+-----------------+-----------------+ >| iterative_solve | OT_STRING | GenericType() | (gmres|bcgstab| | >| rB | | | tfqmr) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_multiste | OT_STRING | "bdf" | Integrator | >| p_method | | | scheme | >| | | | (bdf|adams) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver | OT_STRING | GenericType() | A custom linear | >| | | | solver creator | >| | | | function | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solverB | OT_STRING | GenericType() | A custom linear | >| | | | solver creator | >| | | | function for | >| | | | backwards | >| | | | integration | >| | | | [default: equal | >| | | | to | >| | | | linear_solver] | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_o | OT_DICTIONARY | GenericType() | Options to be | >| ptions | | | passed to the | >| | | | linear solver | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_o | OT_DICTIONARY | GenericType() | Options to be | >| ptionsB | | | passed to the | >| | | | linear solver | >| | | | for backwards | >| | | | integration | >| | | | [default: equal | >| | | | to linear_solve | >| | | | r_options] | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_t | OT_STRING | "dense" | (user_defined|d | >| ype | | | ense|banded|ite | >| | | | rative) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_t | OT_STRING | GenericType() | (user_defined|d | >| ypeB | | | ense|banded|ite | >| | | | rative) | >+-----------------+-----------------+-----------------+-----------------+ >| lower_bandwidth | OT_INTEGER | GenericType() | Lower band- | >| | | | width of banded | >| | | | Jacobian | >| | | | (estimations) | >+-----------------+-----------------+-----------------+-----------------+ >| lower_bandwidth | OT_INTEGER | GenericType() | lower band- | >| B | | | width of banded | >| | | | jacobians for | >| | | | backward | >| | | | integration | >| | | | [default: equal | >| | | | to lower_bandwi | >| | | | dth] | >+-----------------+-----------------+-----------------+-----------------+ >| max_krylov | OT_INTEGER | 10 | Maximum Krylov | >| | | | subspace size | >+-----------------+-----------------+-----------------+-----------------+ >| max_krylovB | OT_INTEGER | GenericType() | Maximum krylov | >| | | | subspace size | >+-----------------+-----------------+-----------------+-----------------+ >| max_multistep_o | OT_INTEGER | 5 | | >| rder | | | | >+-----------------+-----------------+-----------------+-----------------+ >| max_num_steps | OT_INTEGER | 10000 | Maximum number | >| | | | of integrator | >| | | | steps | >+-----------------+-----------------+-----------------+-----------------+ >| nonlinear_solve | OT_STRING | "newton" | (newton|functio | >| r_iteration | | | nal) | >+-----------------+-----------------+-----------------+-----------------+ >| pretype | OT_STRING | "none" | (none|left|righ | >| | | | t|both) | >+-----------------+-----------------+-----------------+-----------------+ >| pretypeB | OT_STRING | GenericType() | (none|left|righ | >| | | | t|both) | >+-----------------+-----------------+-----------------+-----------------+ >| quad_err_con | OT_BOOLEAN | false | Should the | >| | | | quadratures | >| | | | affect the step | >| | | | size control | >+-----------------+-----------------+-----------------+-----------------+ >| reltol | OT_REAL | 0.000 | Relative | >| | | | tolerence for | >| | | | the IVP | >| | | | solution | >+-----------------+-----------------+-----------------+-----------------+ >| reltolB | OT_REAL | GenericType() | Relative | >| | | | tolerence for | >| | | | the adjoint | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to reltol] | >+-----------------+-----------------+-----------------+-----------------+ >| sensitivity_met | OT_STRING | "simultaneous" | (simultaneous|s | >| hod | | | taggered) | >+-----------------+-----------------+-----------------+-----------------+ >| steps_per_check | OT_INTEGER | 20 | Number of steps | >| point | | | between two | >| | | | consecutive | >| | | | checkpoints | >+-----------------+-----------------+-----------------+-----------------+ >| stop_at_end | OT_BOOLEAN | true | Stop the | >| | | | integrator at | >| | | | the end of the | >| | | | interval | >+-----------------+-----------------+-----------------+-----------------+ >| upper_bandwidth | OT_INTEGER | GenericType() | Upper band- | >| | | | width of banded | >| | | | Jacobian | >| | | | (estimations) | >+-----------------+-----------------+-----------------+-----------------+ >| upper_bandwidth | OT_INTEGER | GenericType() | Upper band- | >| B | | | width of banded | >| | | | jacobians for | >| | | | backward | >| | | | integration | >| | | | [default: equal | >| | | | to upper_bandwi | >| | | | dth] | >+-----------------+-----------------+-----------------+-----------------+ >| use_preconditio | OT_BOOLEAN | false | Precondition an | >| ner | | | iterative | >| | | | solver | >+-----------------+-----------------+-----------------+-----------------+ >| use_preconditio | OT_BOOLEAN | GenericType() | Precondition an | >| nerB | | | iterative | >| | | | solver for the | >| | | | backwards | >| | | | problem | >| | | | [default: equal | >| | | | to use_precondi | >| | | | tioner] | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+---------+ >| Id | >+=========+ >| djacB | >+---------+ >| psetupB | >+---------+ >| res | >+---------+ >| resB | >+---------+ >| resQB | >+---------+ >| reset | >+---------+ > >>List of available stats > >+-------------+ >| Id | >+=============+ >| nlinsetups | >+-------------+ >| nlinsetupsB | >+-------------+ >| nsteps | >+-------------+ >| nstepsB | >+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >idas >---- > > > >Interface to IDAS from the Sundials suite. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| abstol | OT_REAL | 0.000 | Absolute | >| | | | tolerence for | >| | | | the IVP | >| | | | solution | >+-----------------+-----------------+-----------------+-----------------+ >| abstolB | OT_REAL | GenericType() | Absolute | >| | | | tolerence for | >| | | | the adjoint | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to abstol] | >+-----------------+-----------------+-----------------+-----------------+ >| abstolv | OT_REALVECTOR | | | >+-----------------+-----------------+-----------------+-----------------+ >| calc_ic | OT_BOOLEAN | true | Use IDACalcIC | >| | | | to get | >| | | | consistent | >| | | | initial | >| | | | conditions. | >+-----------------+-----------------+-----------------+-----------------+ >| calc_icB | OT_BOOLEAN | GenericType() | Use IDACalcIC | >| | | | to get | >| | | | consistent | >| | | | initial | >| | | | conditions for | >| | | | backwards | >| | | | system | >| | | | [default: equal | >| | | | to calc_ic]. | >+-----------------+-----------------+-----------------+-----------------+ >| cj_scaling | OT_BOOLEAN | false | IDAS scaling on | >| | | | cj for the | >| | | | user-defined | >| | | | linear solver | >| | | | module | >+-----------------+-----------------+-----------------+-----------------+ >| disable_interna | OT_BOOLEAN | false | Disable IDAS | >| l_warnings | | | internal | >| | | | warning | >| | | | messages | >+-----------------+-----------------+-----------------+-----------------+ >| exact_jacobian | OT_BOOLEAN | true | Use exact | >| | | | Jacobian | >| | | | information for | >| | | | the forward | >| | | | integration | >+-----------------+-----------------+-----------------+-----------------+ >| exact_jacobianB | OT_BOOLEAN | GenericType() | Use exact | >| | | | Jacobian | >| | | | information for | >| | | | the backward | >| | | | integration | >| | | | [default: equal | >| | | | to | >| | | | exact_jacobian] | >+-----------------+-----------------+-----------------+-----------------+ >| extra_fsens_cal | OT_BOOLEAN | false | Call calc ic an | >| c_ic | | | extra time, | >| | | | with fsens=0 | >+-----------------+-----------------+-----------------+-----------------+ >| finite_differen | OT_BOOLEAN | false | Use finite | >| ce_fsens | | | differences to | >| | | | approximate the | >| | | | forward | >| | | | sensitivity | >| | | | equations (if | >| | | | AD is not | >| | | | available) | >+-----------------+-----------------+-----------------+-----------------+ >| first_time | OT_REAL | GenericType() | First requested | >| | | | time as a | >| | | | fraction of the | >| | | | time interval | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_abstol | OT_REAL | GenericType() | Absolute | >| | | | tolerence for | >| | | | the forward | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to abstol] | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_abstolv | OT_REALVECTOR | | | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_err_con | OT_BOOLEAN | true | include the | >| | | | forward | >| | | | sensitivities | >| | | | in all error | >| | | | controls | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_reltol | OT_REAL | GenericType() | Relative | >| | | | tolerence for | >| | | | the forward | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to reltol] | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_scaling_f | OT_REALVECTOR | GenericType() | Scaling factor | >| actors | | | for the | >| | | | components if | >| | | | finite | >| | | | differences is | >| | | | used | >+-----------------+-----------------+-----------------+-----------------+ >| fsens_sensitivi | OT_INTEGERVECTO | GenericType() | Specifies which | >| y_parameters | R | | components will | >| | | | be used when | >| | | | estimating the | >| | | | sensitivity | >| | | | equations | >+-----------------+-----------------+-----------------+-----------------+ >| init_xdot | OT_REALVECTOR | GenericType() | Initial values | >| | | | for the state | >| | | | derivatives | >+-----------------+-----------------+-----------------+-----------------+ >| interpolation_t | OT_STRING | "hermite" | Type of | >| ype | | | interpolation | >| | | | for the adjoint | >| | | | sensitivities ( | >| | | | hermite|polynom | >| | | | ial) | >+-----------------+-----------------+-----------------+-----------------+ >| iterative_solve | OT_STRING | "gmres" | (gmres|bcgstab| | >| r | | | tfqmr) | >+-----------------+-----------------+-----------------+-----------------+ >| iterative_solve | OT_STRING | GenericType() | (gmres|bcgstab| | >| rB | | | tfqmr) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver | OT_STRING | GenericType() | A custom linear | >| | | | solver creator | >| | | | function | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solverB | OT_STRING | GenericType() | A custom linear | >| | | | solver creator | >| | | | function for | >| | | | backwards | >| | | | integration | >| | | | [default: equal | >| | | | to | >| | | | linear_solver] | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_o | OT_DICTIONARY | GenericType() | Options to be | >| ptions | | | passed to the | >| | | | linear solver | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_o | OT_DICTIONARY | GenericType() | Options to be | >| ptionsB | | | passed to the | >| | | | linear solver | >| | | | for backwards | >| | | | integration | >| | | | [default: equal | >| | | | to linear_solve | >| | | | r_options] | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_t | OT_STRING | "dense" | (user_defined|d | >| ype | | | ense|banded|ite | >| | | | rative) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver_t | OT_STRING | GenericType() | (user_defined|d | >| ypeB | | | ense|banded|ite | >| | | | rative) | >+-----------------+-----------------+-----------------+-----------------+ >| lower_bandwidth | OT_INTEGER | GenericType() | Lower band- | >| | | | width of banded | >| | | | Jacobian | >| | | | (estimations) | >+-----------------+-----------------+-----------------+-----------------+ >| lower_bandwidth | OT_INTEGER | GenericType() | lower band- | >| B | | | width of banded | >| | | | jacobians for | >| | | | backward | >| | | | integration | >| | | | [default: equal | >| | | | to lower_bandwi | >| | | | dth] | >+-----------------+-----------------+-----------------+-----------------+ >| max_krylov | OT_INTEGER | 10 | Maximum Krylov | >| | | | subspace size | >+-----------------+-----------------+-----------------+-----------------+ >| max_krylovB | OT_INTEGER | GenericType() | Maximum krylov | >| | | | subspace size | >+-----------------+-----------------+-----------------+-----------------+ >| max_multistep_o | OT_INTEGER | 5 | | >| rder | | | | >+-----------------+-----------------+-----------------+-----------------+ >| max_num_steps | OT_INTEGER | 10000 | Maximum number | >| | | | of integrator | >| | | | steps | >+-----------------+-----------------+-----------------+-----------------+ >| max_step_size | OT_REAL | 0 | Maximim step | >| | | | size | >+-----------------+-----------------+-----------------+-----------------+ >| pretype | OT_STRING | "none" | (none|left|righ | >| | | | t|both) | >+-----------------+-----------------+-----------------+-----------------+ >| pretypeB | OT_STRING | GenericType() | (none|left|righ | >| | | | t|both) | >+-----------------+-----------------+-----------------+-----------------+ >| quad_err_con | OT_BOOLEAN | false | Should the | >| | | | quadratures | >| | | | affect the step | >| | | | size control | >+-----------------+-----------------+-----------------+-----------------+ >| reltol | OT_REAL | 0.000 | Relative | >| | | | tolerence for | >| | | | the IVP | >| | | | solution | >+-----------------+-----------------+-----------------+-----------------+ >| reltolB | OT_REAL | GenericType() | Relative | >| | | | tolerence for | >| | | | the adjoint | >| | | | sensitivity | >| | | | solution | >| | | | [default: equal | >| | | | to reltol] | >+-----------------+-----------------+-----------------+-----------------+ >| sensitivity_met | OT_STRING | "simultaneous" | (simultaneous|s | >| hod | | | taggered) | >+-----------------+-----------------+-----------------+-----------------+ >| steps_per_check | OT_INTEGER | 20 | Number of steps | >| point | | | between two | >| | | | consecutive | >| | | | checkpoints | >+-----------------+-----------------+-----------------+-----------------+ >| stop_at_end | OT_BOOLEAN | true | Stop the | >| | | | integrator at | >| | | | the end of the | >| | | | interval | >+-----------------+-----------------+-----------------+-----------------+ >| suppress_algebr | OT_BOOLEAN | false | Supress | >| aic | | | algebraic | >| | | | variables in | >| | | | the error | >| | | | testing | >+-----------------+-----------------+-----------------+-----------------+ >| upper_bandwidth | OT_INTEGER | GenericType() | Upper band- | >| | | | width of banded | >| | | | Jacobian | >| | | | (estimations) | >+-----------------+-----------------+-----------------+-----------------+ >| upper_bandwidth | OT_INTEGER | GenericType() | Upper band- | >| B | | | width of banded | >| | | | jacobians for | >| | | | backward | >| | | | integration | >| | | | [default: equal | >| | | | to upper_bandwi | >| | | | dth] | >+-----------------+-----------------+-----------------+-----------------+ >| use_preconditio | OT_BOOLEAN | false | Precondition an | >| ner | | | iterative | >| | | | solver | >+-----------------+-----------------+-----------------+-----------------+ >| use_preconditio | OT_BOOLEAN | GenericType() | Precondition an | >| nerB | | | iterative | >| | | | solver for the | >| | | | backwards | >| | | | problem | >| | | | [default: equal | >| | | | to use_precondi | >| | | | tioner] | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+--------------------------+ >| Id | >+==========================+ >| bjacB | >+--------------------------+ >| correctInitialConditions | >+--------------------------+ >| jtimesB | >+--------------------------+ >| psetup | >+--------------------------+ >| psetupB | >+--------------------------+ >| psolveB | >+--------------------------+ >| res | >+--------------------------+ >| resB | >+--------------------------+ >| resS | >+--------------------------+ >| rhsQB | >+--------------------------+ > >>List of available stats > >+-------------+ >| Id | >+=============+ >| nlinsetups | >+-------------+ >| nlinsetupsB | >+-------------+ >| nsteps | >+-------------+ >| nstepsB | >+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >collocation >----------- > > > >Fixed-step implicit Runge-Kutta integrator ODE/DAE integrator based on >collocation schemes > >The method is still under development > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| collocation_sch | OT_STRING | "radau" | Collocation | >| eme | | | scheme (radau|l | >| | | | egendre) | >+-----------------+-----------------+-----------------+-----------------+ >| implicit_solver | OT_STRING | GenericType() | An implicit | >| | | | function solver | >+-----------------+-----------------+-----------------+-----------------+ >| implicit_solver | OT_DICTIONARY | GenericType() | Options to be | >| _options | | | passed to the | >| | | | NLP Solver | >+-----------------+-----------------+-----------------+-----------------+ >| interpolation_o | OT_INTEGER | 3 | Order of the | >| rder | | | interpolating | >| | | | polynomials | >+-----------------+-----------------+-----------------+-----------------+ >| number_of_finit | OT_INTEGER | 20 | Number of | >| e_elements | | | finite elements | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >oldcollocation >-------------- > > > >Collocation integrator ODE/DAE integrator based on collocation > >The method is still under development > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| collocation_sch | OT_STRING | "radau" | Collocation | >| eme | | | scheme (radau|l | >| | | | egendre) | >+-----------------+-----------------+-----------------+-----------------+ >| expand_f | OT_BOOLEAN | false | Expand the | >| | | | ODE/DAE | >| | | | residual | >| | | | function in an | >| | | | SX graph | >+-----------------+-----------------+-----------------+-----------------+ >| expand_q | OT_BOOLEAN | false | Expand the | >| | | | quadrature | >| | | | function in an | >| | | | SX graph | >+-----------------+-----------------+-----------------+-----------------+ >| hotstart | OT_BOOLEAN | true | Initialize the | >| | | | trajectory at | >| | | | the previous | >| | | | solution | >+-----------------+-----------------+-----------------+-----------------+ >| implicit_solver | OT_STRING | GenericType() | An implicit | >| | | | function solver | >+-----------------+-----------------+-----------------+-----------------+ >| implicit_solver | OT_DICTIONARY | GenericType() | Options to be | >| _options | | | passed to the | >| | | | implicit solver | >+-----------------+-----------------+-----------------+-----------------+ >| interpolation_o | OT_INTEGER | 3 | Order of the | >| rder | | | interpolating | >| | | | polynomials | >+-----------------+-----------------+-----------------+-----------------+ >| number_of_finit | OT_INTEGER | 20 | Number of | >| e_elements | | | finite elements | >+-----------------+-----------------+-----------------+-----------------+ >| startup_integra | OT_STRING | GenericType() | An ODE/DAE | >| tor | | | integrator that | >| | | | can be used to | >| | | | generate a | >| | | | startup | >| | | | trajectory | >+-----------------+-----------------+-----------------+-----------------+ >| startup_integra | OT_DICTIONARY | GenericType() | Options to be | >| tor_options | | | passed to the | >| | | | startup | >| | | | integrator | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >rk -- > > > >Fixed-step explicit Runge-Kutta integrator for ODEs Currently implements >RK4. > >The method is still under development > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| number_of_finit | OT_INTEGER | 20 | Number of | >| e_elements | | | finite elements | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: integrator.hpp -} newtype Integrator = Integrator (ForeignPtr Integrator') -- typeclass decl class IntegratorClass a where castIntegrator :: a -> Integrator instance IntegratorClass Integrator where castIntegrator = id -- baseclass instances instance FunctionClass Integrator where castFunction (Integrator x) = Function (castForeignPtr x) instance OptionsFunctionalityClass Integrator where castOptionsFunctionality (Integrator x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass Integrator where castPrintableObject (Integrator x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Integrator where castSharedObject (Integrator x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass Integrator where castIOInterfaceFunction (Integrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal Integrator (Ptr Integrator') where marshal (Integrator x) = return (unsafeForeignPtrToPtr x) marshalFree (Integrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Integrator" c_delete_casadi__Integrator :: FunPtr (Ptr Integrator' -> IO ()) instance WrapReturn (Ptr Integrator') Integrator where wrapReturn = (fmap Integrator) . (newForeignPtr c_delete_casadi__Integrator) -- raw decl data LinearSolver' -- data decl {-| >Base class for the linear solver classes. > >Solves the linear system A*X = B or A^T*X = B for X with A square and non- >singular > >If A is structurally singular, an error will be thrown during init. If A is >numerically singular, the prepare step will fail. > >The usual procedure to use LinearSolver is: init() > >set the first input (A) > >prepare() > >set the second input (b) > >solve() > >Repeat steps 4 and 5 to work with other b vectors. > >The method evaluate() combines the prepare() and solve() step and is >therefore more expensive if A is invariant. > >General information >=================== > > > >>Input scheme: casadi::LinsolInput (LINSOL_NUM_IN = 2) [linsolIn] > >+-----------+-------+------------------------------------------------+ >| Full name | Short | Description | >+===========+=======+================================================+ >| LINSOL_A | A | The square matrix A: sparse, (n x n). . | >+-----------+-------+------------------------------------------------+ >| LINSOL_B | B | The right-hand-side matrix b: dense, (n x m) . | >+-----------+-------+------------------------------------------------+ > >>Output scheme: casadi::LinsolOutput (LINSOL_NUM_OUT = 1) [linsolOut] > >+-----------+-------+----------------------------------------------+ >| Full name | Short | Description | >+===========+=======+==============================================+ >| LINSOL_X | X | Solution to the linear system of equations . | >+-----------+-------+----------------------------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- csparsecholesky > >- csparse > >- lapacklu > >- lapackqr > >- symbolicqr > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >LinearSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >csparsecholesky >--------------- > > > >LinearSolver with CSparseCholesky Interface > >>List of available options > >+----+------+---------+-------------+ >| Id | Type | Default | Description | >+====+======+=========+=============+ >+----+------+---------+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >csparse >------- > > > >LinearSolver with CSparse Interface > >>List of available options > >+----+------+---------+-------------+ >| Id | Type | Default | Description | >+====+======+=========+=============+ >+----+------+---------+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >lapacklu >-------- > > > >This class solves the linear system A.x=b by making an LU factorization of >A: A = L.U, with L lower and U upper triangular > >>List of available options > >+-----------------------------+------------+---------+-------------+ >| Id | Type | Default | Description | >+=============================+============+=========+=============+ >| allow_equilibration_failure | OT_BOOLEAN | false | | >+-----------------------------+------------+---------+-------------+ >| equilibration | OT_BOOLEAN | true | | >+-----------------------------+------------+---------+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >lapackqr >-------- > > > >This class solves the linear system A.x=b by making an QR factorization of >A: A = Q.R, with Q orthogonal and R upper triangular > >>List of available options > >+----+------+---------+-------------+ >| Id | Type | Default | Description | >+====+======+=========+=============+ >+----+------+---------+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >symbolicqr >---------- > > > >LinearSolver based on QR factorization with sparsity pattern based >reordering without partial pivoting > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| codegen | OT_BOOLEAN | false | C-code | >| | | | generation | >+-----------------+-----------------+-----------------+-----------------+ >| compiler | OT_STRING | "gcc -fPIC -O2" | Compiler | >| | | | command to be | >| | | | used for | >| | | | compiling | >| | | | generated code | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: linear_solver.hpp -} newtype LinearSolver = LinearSolver (ForeignPtr LinearSolver') -- typeclass decl class LinearSolverClass a where castLinearSolver :: a -> LinearSolver instance LinearSolverClass LinearSolver where castLinearSolver = id -- baseclass instances instance FunctionClass LinearSolver where castFunction (LinearSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass LinearSolver where castOptionsFunctionality (LinearSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass LinearSolver where castPrintableObject (LinearSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass LinearSolver where castSharedObject (LinearSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass LinearSolver where castIOInterfaceFunction (LinearSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal LinearSolver (Ptr LinearSolver') where marshal (LinearSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (LinearSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__LinearSolver" c_delete_casadi__LinearSolver :: FunPtr (Ptr LinearSolver' -> IO ()) instance WrapReturn (Ptr LinearSolver') LinearSolver where wrapReturn = (fmap LinearSolver) . (newForeignPtr c_delete_casadi__LinearSolver) -- raw decl data LpSolver' -- data decl {-| >LpSolver. > >Solves the following linear problem: > > > >:: > > min c' x > x > > subject to > LBA <= A x <= UBA > LBX <= x <= UBX > > with x ( n x 1) > c ( n x 1 ) > A sparse matrix ( nc x n) > LBA, UBA dense vector (nc x 1) > LBX, UBX dense vector (n x 1) > > n: number of decision variables (x) > nc: number of constraints (A) > > > >General information >=================== > > > >>Input scheme: casadi::LpSolverInput (LP_SOLVER_NUM_IN = 6) [lpIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| LP_SOLVER_C | c | The vector c: dense (n | >| | | x 1) . | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_A | a | The matrix A: sparse, | >| | | (nc x n) - product | >| | | with x must be dense. | >| | | . | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_LBA | lba | dense, (nc x 1) | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_UBA | uba | dense, (nc x 1) | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_LBX | lbx | dense, (n x 1) | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_UBX | ubx | dense, (n x 1) | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::LpSolverOutput (LP_SOLVER_NUM_OUT = 4) [lpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| LP_SOLVER_X | x | The primal solution . | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_COST | cost | The optimal cost . | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_LAM_A | lam_a | The dual solution | >| | | corresponding to | >| | | linear bounds . | >+------------------------+------------------------+------------------------+ >| LP_SOLVER_LAM_X | lam_x | The dual solution | >| | | corresponding to | >| | | simple bounds . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- qp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >LpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >qp -- > > > >Solve LPs using a QpSolver > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| qp_solver | OT_STRING | GenericType() | The QPSOlver | >| | | | used to solve | >| | | | the LPs. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_solver_optio | OT_DICTIONARY | GenericType() | Options to be | >| ns | | | passed to the | >| | | | QPSOlver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+-----------------+ >| Id | >+=================+ >| qp_solver_stats | >+-----------------+ > >-------------------------------------------------------------------------------- > > > >Joris Gillis >Diagrams >-------- > > > >C++ includes: lp_solver.hpp -} newtype LpSolver = LpSolver (ForeignPtr LpSolver') -- typeclass decl class LpSolverClass a where castLpSolver :: a -> LpSolver instance LpSolverClass LpSolver where castLpSolver = id -- baseclass instances instance FunctionClass LpSolver where castFunction (LpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass LpSolver where castOptionsFunctionality (LpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass LpSolver where castPrintableObject (LpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass LpSolver where castSharedObject (LpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass LpSolver where castIOInterfaceFunction (LpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal LpSolver (Ptr LpSolver') where marshal (LpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (LpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__LpSolver" c_delete_casadi__LpSolver :: FunPtr (Ptr LpSolver' -> IO ()) instance WrapReturn (Ptr LpSolver') LpSolver where wrapReturn = (fmap LpSolver) . (newForeignPtr c_delete_casadi__LpSolver) -- raw decl data MX' -- data decl {-| -} newtype MX = MX (ForeignPtr MX') -- typeclass decl class MXClass a where castMX :: a -> MX instance MXClass MX where castMX = id -- baseclass instances instance PrintableObjectClass MX where castPrintableObject (MX x) = PrintableObject (castForeignPtr x) instance SharedObjectClass MX where castSharedObject (MX x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal MX (Ptr MX') where marshal (MX x) = return (unsafeForeignPtrToPtr x) marshalFree (MX x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__MX" c_delete_casadi__MX :: FunPtr (Ptr MX' -> IO ()) instance WrapReturn (Ptr MX') MX where wrapReturn = (fmap MX) . (newForeignPtr c_delete_casadi__MX) -- raw decl data MXFunction' -- data decl {-| >General function mapping from/to MX. > >Joel Andersson > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: mx_function.hpp -} newtype MXFunction = MXFunction (ForeignPtr MXFunction') -- typeclass decl class MXFunctionClass a where castMXFunction :: a -> MXFunction instance MXFunctionClass MXFunction where castMXFunction = id -- baseclass instances instance FunctionClass MXFunction where castFunction (MXFunction x) = Function (castForeignPtr x) instance OptionsFunctionalityClass MXFunction where castOptionsFunctionality (MXFunction x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass MXFunction where castPrintableObject (MXFunction x) = PrintableObject (castForeignPtr x) instance SharedObjectClass MXFunction where castSharedObject (MXFunction x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass MXFunction where castIOInterfaceFunction (MXFunction x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal MXFunction (Ptr MXFunction') where marshal (MXFunction x) = return (unsafeForeignPtrToPtr x) marshalFree (MXFunction x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__MXFunction" c_delete_casadi__MXFunction :: FunPtr (Ptr MXFunction' -> IO ()) instance WrapReturn (Ptr MXFunction') MXFunction where wrapReturn = (fmap MXFunction) . (newForeignPtr c_delete_casadi__MXFunction) -- raw decl data NlpSolver' -- data decl {-| >NlpSolver. > >Solves the following parametric nonlinear program (NLP): > >:: > > min F(x, p) > x > > subject to > LBX <= x <= UBX > LBG <= G(x, p) <= UBG > p == P > > nx: number of decision variables > ng: number of constraints > np: number of parameters > > > > >General information >=================== > > > >>Input scheme: casadi::NlpSolverInput (NLP_SOLVER_NUM_IN = 8) [nlpSolverIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| NLP_SOLVER_X0 | x0 | Decision variables, | >| | | initial guess (nx x 1) | >| | | . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_P | p | Value of fixed | >| | | parameters (np x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LBX | lbx | Decision variables | >| | | lower bound (nx x 1), | >| | | default -inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_UBX | ubx | Decision variables | >| | | upper bound (nx x 1), | >| | | default +inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LBG | lbg | Constraints lower | >| | | bound (ng x 1), | >| | | default -inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_UBG | ubg | Constraints upper | >| | | bound (ng x 1), | >| | | default +inf . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_X0 | lam_x0 | Lagrange multipliers | >| | | for bounds on X, | >| | | initial guess (nx x 1) | >| | | . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_G0 | lam_g0 | Lagrange multipliers | >| | | for bounds on G, | >| | | initial guess (ng x 1) | >| | | . | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::NlpSolverOutput (NLP_SOLVER_NUM_OUT = 6) [nlpSolverOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| NLP_SOLVER_X | x | Decision variables at | >| | | the optimal solution | >| | | (nx x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_F | f | Cost function value at | >| | | the optimal solution | >| | | (1 x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_G | g | Constraints function | >| | | at the optimal | >| | | solution (ng x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_X | lam_x | Lagrange multipliers | >| | | for bounds on X at the | >| | | solution (nx x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_G | lam_g | Lagrange multipliers | >| | | for bounds on G at the | >| | | solution (ng x 1) . | >+------------------------+------------------------+------------------------+ >| NLP_SOLVER_LAM_P | lam_p | Lagrange multipliers | >| | | for bounds on P at the | >| | | solution (np x 1) . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| eval_errors_ | OT_BOOLEAN | false | When errors | casadi::NlpS | >| fatal | | | occur during | olverInterna | >| | | | evaluation | l | >| | | | of | | >| | | | f,g,...,stop | | >| | | | the | | >| | | | iterations | | >+--------------+--------------+--------------+--------------+--------------+ >| expand | OT_BOOLEAN | false | Expand the | casadi::NlpS | >| | | | NLP function | olverInterna | >| | | | in terms of | l | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| grad_f | OT_FUNCTION | GenericType( | Function for | casadi::NlpS | >| | | ) | calculating | olverInterna | >| | | | the gradient | l | >| | | | of the | | >| | | | objective | | >| | | | (column, aut | | >| | | | ogenerated | | >| | | | by default) | | >+--------------+--------------+--------------+--------------+--------------+ >| grad_lag | OT_FUNCTION | GenericType( | Function for | casadi::NlpS | >| | | ) | calculating | olverInterna | >| | | | the gradient | l | >| | | | of the | | >| | | | Lagrangian ( | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| hess_lag | OT_FUNCTION | GenericType( | Function for | casadi::NlpS | >| | | ) | calculating | olverInterna | >| | | | the Hessian | l | >| | | | of the | | >| | | | Lagrangian ( | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| ignore_check | OT_BOOLEAN | false | If set to | casadi::NlpS | >| _vec | | | true, the | olverInterna | >| | | | input shape | l | >| | | | of F will | | >| | | | not be | | >| | | | checked. | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| iteration_ca | OT_CALLBACK | GenericType( | A function | casadi::NlpS | >| llback | | ) | that will be | olverInterna | >| | | | called at | l | >| | | | each | | >| | | | iteration | | >| | | | with the | | >| | | | solver as | | >| | | | input. Check | | >| | | | documentatio | | >| | | | n of | | >| | | | Callback . | | >+--------------+--------------+--------------+--------------+--------------+ >| iteration_ca | OT_BOOLEAN | false | If set to | casadi::NlpS | >| llback_ignor | | | true, errors | olverInterna | >| e_errors | | | thrown by it | l | >| | | | eration_call | | >| | | | back will be | | >| | | | ignored. | | >+--------------+--------------+--------------+--------------+--------------+ >| iteration_ca | OT_INTEGER | 1 | Only call | casadi::NlpS | >| llback_step | | | the callback | olverInterna | >| | | | function | l | >| | | | every few | | >| | | | iterations. | | >+--------------+--------------+--------------+--------------+--------------+ >| jac_f | OT_FUNCTION | GenericType( | Function for | casadi::NlpS | >| | | ) | calculating | olverInterna | >| | | | the jacobian | l | >| | | | of the | | >| | | | objective | | >| | | | (sparse row, | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| jac_g | OT_FUNCTION | GenericType( | Function for | casadi::NlpS | >| | | ) | calculating | olverInterna | >| | | | the Jacobian | l | >| | | | of the | | >| | | | constraints | | >| | | | (autogenerat | | >| | | | ed by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ >| warn_initial | OT_BOOLEAN | false | Warn if the | casadi::NlpS | >| _bounds | | | initial | olverInterna | >| | | | guess does | l | >| | | | not satisfy | | >| | | | LBX and UBX | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- ipopt > >- knitro > >- snopt > >- worhp > >- scpgen > >- sqpmethod > >- stabilizedsqp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >NlpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >ipopt >----- > > > >When in warmstart mode, output NLP_SOLVER_LAM_X may be used as input > >NOTE: Even when max_iter == 0, it is not guaranteed that >input(NLP_SOLVER_X0) == output(NLP_SOLVER_X). Indeed if bounds on X or >constraints are unmet, they will differ. > >For a good tutorial on IPOPT, >seehttp://drops.dagstuhl.de/volltexte/2009/2089/pdf/09061.WaechterAndreas.Paper.2089.pdf > >A good resource about the algorithms in IPOPT is: Wachter and L. T. Biegler, >On the Implementation of an Interior-Point Filter Line-Search Algorithm for >Large-Scale Nonlinear Programming, Mathematical Programming 106(1), pp. >25-57, 2006 (As Research Report RC 23149, IBM T. J. Watson Research Center, >Yorktown, USA > >Caveats: with default options, multipliers for the decision variables are >wrong for equality constraints. Change the 'fixed_variable_treatment' to >'make_constraint' or 'relax_bounds' to obtain correct results. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| accept_after_ma | OT_INTEGER | -1 | Accept a trial | >| x_steps | | | point after | >| | | | maximal this | >| | | | number of | >| | | | steps. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| accept_every_tr | OT_STRING | no | Always accept | >| ial_step | | | the first trial | >| | | | step. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| acceptable_comp | OT_REAL | 0.010 | "Acceptance" | >| l_inf_tol | | | threshold for | >| | | | the | >| | | | complementarity | >| | | | conditions. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| acceptable_cons | OT_REAL | 0.010 | "Acceptance" | >| tr_viol_tol | | | threshold for | >| | | | the constraint | >| | | | violation. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| acceptable_dual | OT_REAL | 1.000e+10 | "Acceptance" | >| _inf_tol | | | threshold for | >| | | | the dual | >| | | | infeasibility. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| acceptable_iter | OT_INTEGER | 15 | Number of | >| | | | "acceptable" | >| | | | iterates before | >| | | | triggering | >| | | | termination. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| acceptable_obj_ | OT_REAL | 1.000e+20 | "Acceptance" | >| change_tol | | | stopping | >| | | | criterion based | >| | | | on objective | >| | | | function | >| | | | change. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| acceptable_tol | OT_REAL | 0.000 | "Acceptable" | >| | | | convergence | >| | | | tolerance | >| | | | (relative). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| adaptive_mu_glo | OT_STRING | obj-constr- | Globalization | >| balization | | filter | strategy for | >| | | | the adaptive mu | >| | | | selection mode. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| adaptive_mu_kkt | OT_STRING | 2-norm-squared | Norm used for | >| _norm_type | | | the KKT error | >| | | | in the adaptive | >| | | | mu | >| | | | globalization | >| | | | strategies. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| adaptive_mu_kkt | OT_REAL | 1.000 | Sufficient | >| error_red_fact | | | decrease factor | >| | | | for "kkt-error" | >| | | | globalization | >| | | | strategy. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| adaptive_mu_kkt | OT_INTEGER | 4 | Maximum number | >| error_red_iters | | | of iterations | >| | | | requiring | >| | | | sufficient | >| | | | progress. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| adaptive_mu_mon | OT_REAL | 0.800 | Determines the | >| otone_init_fact | | | initial value | >| or | | | of the barrier | >| | | | parameter when | >| | | | switching to | >| | | | the monotone | >| | | | mode. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| adaptive_mu_res | OT_STRING | no | Indicates if | >| tore_previous_i | | | the previous | >| terate | | | iterate should | >| | | | be restored if | >| | | | the monotone | >| | | | mode is | >| | | | entered. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| adaptive_mu_saf | OT_REAL | 0 | (see IPOPT | >| eguard_factor | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| alpha_for_y | OT_STRING | primal | Method to | >| | | | determine the | >| | | | step size for | >| | | | constraint | >| | | | multipliers. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| alpha_for_y_tol | OT_REAL | 10 | Tolerance for | >| | | | switching to | >| | | | full equality | >| | | | multiplier | >| | | | steps. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| alpha_min_frac | OT_REAL | 0.050 | Safety factor | >| | | | for the minimal | >| | | | step size | >| | | | (before | >| | | | switching to | >| | | | restoration | >| | | | phase). (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| alpha_red_facto | OT_REAL | 0.500 | Fractional | >| r | | | reduction of | >| | | | the trial step | >| | | | size in the | >| | | | backtracking | >| | | | line search. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| barrier_tol_fac | OT_REAL | 10 | Factor for mu | >| tor | | | in barrier stop | >| | | | test. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| bound_frac | OT_REAL | 0.010 | Desired minimum | >| | | | relative | >| | | | distance from | >| | | | the initial | >| | | | point to bound. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| bound_mult_init | OT_STRING | constant | Initialization | >| _method | | | method for | >| | | | bound | >| | | | multipliers | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| bound_mult_init | OT_REAL | 1 | Initial value | >| _val | | | for the bound | >| | | | multipliers. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| bound_mult_rese | OT_REAL | 1000 | Threshold for | >| t_threshold | | | resetting bound | >| | | | multipliers | >| | | | after the | >| | | | restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| bound_push | OT_REAL | 0.010 | Desired minimum | >| | | | absolute | >| | | | distance from | >| | | | the initial | >| | | | point to bound. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| bound_relax_fac | OT_REAL | 0.000 | Factor for | >| tor | | | initial | >| | | | relaxation of | >| | | | the bounds. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| check_derivativ | OT_STRING | no | Indicates | >| es_for_naninf | | | whether it is | >| | | | desired to | >| | | | check for | >| | | | Nan/Inf in | >| | | | derivative | >| | | | matrices (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| chi_cup | OT_REAL | 1.500 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| chi_hat | OT_REAL | 2 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| chi_tilde | OT_REAL | 5 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| compl_inf_tol | OT_REAL | 0.000 | Desired | >| | | | threshold for | >| | | | the | >| | | | complementarity | >| | | | conditions. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| con_integer_md | OT_DICTIONARY | None | Integer | >| | | | metadata (a | >| | | | dictionary with | >| | | | lists of | >| | | | integers) about | >| | | | constraints to | >| | | | be passed to | >| | | | IPOPT | >+-----------------+-----------------+-----------------+-----------------+ >| con_numeric_md | OT_DICTIONARY | None | Numeric | >| | | | metadata (a | >| | | | dictionary with | >| | | | lists of reals) | >| | | | about | >| | | | constraints to | >| | | | be passed to | >| | | | IPOPT | >+-----------------+-----------------+-----------------+-----------------+ >| con_string_md | OT_DICTIONARY | None | String metadata | >| | | | (a dictionary | >| | | | with lists of | >| | | | strings) about | >| | | | constraints to | >| | | | be passed to | >| | | | IPOPT | >+-----------------+-----------------+-----------------+-----------------+ >| constr_mult_ini | OT_REAL | 1000 | Maximum allowed | >| t_max | | | least-square | >| | | | guess of | >| | | | constraint | >| | | | multipliers. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| constr_mult_res | OT_REAL | 0 | Threshold for | >| et_threshold | | | resetting | >| | | | equality and | >| | | | inequality | >| | | | multipliers | >| | | | after | >| | | | restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| constr_viol_tol | OT_REAL | 0.000 | Desired | >| | | | threshold for | >| | | | the constraint | >| | | | violation. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| constraint_viol | OT_STRING | 1-norm | Norm to be used | >| ation_norm_type | | | for the | >| | | | constraint | >| | | | violation in | >| | | | the line | >| | | | search. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| corrector_compl | OT_REAL | 1 | Complementarity | >| _avrg_red_fact | | | tolerance | >| | | | factor for | >| | | | accepting | >| | | | corrector step | >| | | | (unsupported!). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| corrector_type | OT_STRING | none | The type of | >| | | | corrector steps | >| | | | that should be | >| | | | taken | >| | | | (unsupported!). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| delta | OT_REAL | 1 | Multiplier for | >| | | | constraint | >| | | | violation in | >| | | | the switching | >| | | | rule. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| delta_y_max | OT_REAL | 1.000e+12 | a parameter | >| | | | used to check | >| | | | if the fast | >| | | | direction can | >| | | | be used asthe | >| | | | line search | >| | | | direction (for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| dependency_dete | OT_STRING | no | Indicates if | >| ction_with_rhs | | | the right hand | >| | | | sides of the | >| | | | constraints | >| | | | should be | >| | | | considered | >| | | | during | >| | | | dependency | >| | | | detection (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| dependency_dete | OT_STRING | none | Indicates which | >| ctor | | | linear solver | >| | | | should be used | >| | | | to detect | >| | | | linearly | >| | | | dependent | >| | | | equality | >| | | | constraints. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| derivative_test | OT_STRING | none | Enable | >| | | | derivative | >| | | | checker (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| derivative_test | OT_INTEGER | -2 | Index of first | >| _first_index | | | quantity to be | >| | | | checked by | >| | | | derivative | >| | | | checker (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| derivative_test | OT_REAL | 0.000 | Size of the | >| _perturbation | | | finite | >| | | | difference | >| | | | perturbation in | >| | | | derivative | >| | | | test. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| derivative_test | OT_STRING | no | Indicates | >| _print_all | | | whether | >| | | | information for | >| | | | all estimated | >| | | | derivatives | >| | | | should be | >| | | | printed. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| derivative_test | OT_REAL | 0.000 | Threshold for | >| _tol | | | indicating | >| | | | wrong | >| | | | derivative. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| diverging_itera | OT_REAL | 1.000e+20 | Threshold for | >| tes_tol | | | maximal value | >| | | | of primal | >| | | | iterates. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| dual_inf_tol | OT_REAL | 1 | Desired | >| | | | threshold for | >| | | | the dual | >| | | | infeasibility. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| epsilon_c | OT_REAL | 0.010 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| eta_min | OT_REAL | 10 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| eta_penalty | OT_REAL | 0.000 | Relaxation | >| | | | factor in the | >| | | | Armijo | >| | | | condition for | >| | | | the penalty | >| | | | function. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| eta_phi | OT_REAL | 0.000 | Relaxation | >| | | | factor in the | >| | | | Armijo | >| | | | condition. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| evaluate_orig_o | OT_STRING | yes | Determines if | >| bj_at_resto_tri | | | the original | >| al | | | objective | >| | | | function should | >| | | | be evaluated at | >| | | | restoration | >| | | | phase trial | >| | | | points. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| expect_infeasib | OT_STRING | no | Enable | >| le_problem | | | heuristics to | >| | | | quickly detect | >| | | | an infeasible | >| | | | problem. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| expect_infeasib | OT_REAL | 0.001 | Threshold for | >| le_problem_ctol | | | disabling "expe | >| | | | ct_infeasible_p | >| | | | roblem" option. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| expect_infeasib | OT_REAL | 100000000 | Multiplier | >| le_problem_ytol | | | threshold for | >| | | | activating "exp | >| | | | ect_infeasible_ | >| | | | problem" | >| | | | option. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| fast_des_fact | OT_REAL | 0.100 | a parameter | >| | | | used to check | >| | | | if the fast | >| | | | direction can | >| | | | be used asthe | >| | | | line search | >| | | | direction (for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| fast_step_compu | OT_STRING | no | Indicates if | >| tation | | | the linear | >| | | | system should | >| | | | be solved | >| | | | quickly. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| file_print_leve | OT_INTEGER | 5 | Verbosity level | >| l | | | for output | >| | | | file. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| filter_margin_f | OT_REAL | 0.000 | Factor | >| act | | | determining | >| | | | width of margin | >| | | | for obj-constr- | >| | | | filter adaptive | >| | | | globalization | >| | | | strategy. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| filter_max_marg | OT_REAL | 1 | Maximum width | >| in | | | of margin in | >| | | | obj-constr- | >| | | | filter adaptive | >| | | | globalization | >| | | | strategy. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| filter_reset_tr | OT_INTEGER | 5 | Number of | >| igger | | | iterations that | >| | | | trigger the | >| | | | filter reset. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| findiff_perturb | OT_REAL | 0.000 | Size of the | >| ation | | | finite | >| | | | difference | >| | | | perturbation | >| | | | for derivative | >| | | | approximation. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| first_hessian_p | OT_REAL | 0.000 | Size of first | >| erturbation | | | x-s | >| | | | perturbation | >| | | | tried. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| fixed_mu_oracle | OT_STRING | average_compl | Oracle for the | >| | | | barrier | >| | | | parameter when | >| | | | switching to | >| | | | fixed mode. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| fixed_variable_ | OT_STRING | make_parameter | Determines how | >| treatment | | | fixed variables | >| | | | should be | >| | | | handled. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| gamma_hat | OT_REAL | 0.040 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| gamma_phi | OT_REAL | 0.000 | Relaxation | >| | | | factor in the | >| | | | filter margin | >| | | | for the barrier | >| | | | function. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| gamma_theta | OT_REAL | 0.000 | Relaxation | >| | | | factor in the | >| | | | filter margin | >| | | | for the | >| | | | constraint | >| | | | violation. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| gamma_tilde | OT_REAL | 4 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| hessian_approxi | OT_STRING | exact | Indicates what | >| mation | | | Hessian | >| | | | information is | >| | | | to be used. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| hessian_approxi | OT_STRING | nonlinear- | Indicates in | >| mation_space | | variables | which subspace | >| | | | the Hessian | >| | | | information is | >| | | | to be | >| | | | approximated. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| hessian_constan | OT_STRING | no | Indicates | >| t | | | whether the | >| | | | problem is a | >| | | | quadratic | >| | | | problem (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| honor_original_ | OT_STRING | yes | Indicates | >| bounds | | | whether final | >| | | | points should | >| | | | be projected | >| | | | into original | >| | | | bounds. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| inf_pr_output | OT_STRING | original | Determines what | >| | | | value is | >| | | | printed in the | >| | | | "inf_pr" output | >| | | | column. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| jac_c_constant | OT_STRING | no | Indicates | >| | | | whether all | >| | | | equality | >| | | | constraints are | >| | | | linear (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| jac_d_constant | OT_STRING | no | Indicates | >| | | | whether all | >| | | | inequality | >| | | | constraints are | >| | | | linear (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| jacobian_approx | OT_STRING | exact | Specifies | >| imation | | | technique to | >| | | | compute | >| | | | constraint | >| | | | Jacobian (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| jacobian_regula | OT_REAL | 0.250 | Exponent for mu | >| rization_expone | | | in the | >| nt | | | regularization | >| | | | for rank- | >| | | | deficient | >| | | | constraint | >| | | | Jacobians. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| jacobian_regula | OT_REAL | 0.000 | Size of the | >| rization_value | | | regularization | >| | | | for rank- | >| | | | deficient | >| | | | constraint | >| | | | Jacobians. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| kappa_d | OT_REAL | 0.000 | Weight for | >| | | | linear damping | >| | | | term (to handle | >| | | | one-sided | >| | | | bounds). (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| kappa_sigma | OT_REAL | 1.000e+10 | Factor limiting | >| | | | the deviation | >| | | | of dual | >| | | | variables from | >| | | | primal | >| | | | estimates. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| kappa_soc | OT_REAL | 0.990 | Factor in the | >| | | | sufficient | >| | | | reduction rule | >| | | | for second | >| | | | order | >| | | | correction. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| kappa_x_dis | OT_REAL | 100 | a parameter | >| | | | used to check | >| | | | if the fast | >| | | | direction can | >| | | | be used asthe | >| | | | line search | >| | | | direction (for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| kappa_y_dis | OT_REAL | 10000 | a parameter | >| | | | used to check | >| | | | if the fast | >| | | | direction can | >| | | | be used asthe | >| | | | line search | >| | | | direction (for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| least_square_in | OT_STRING | no | Least square | >| it_duals | | | initialization | >| | | | of all dual | >| | | | variables (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| least_square_in | OT_STRING | no | Least square | >| it_primal | | | initialization | >| | | | of the primal | >| | | | variables (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_STRING | sherman- | Strategy for | >| aug_solver | | morrison | solving the | >| | | | augmented | >| | | | system for low- | >| | | | rank Hessian. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_REAL | 1 | Value for B0 in | >| init_val | | | low-rank | >| | | | update. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_REAL | 100000000 | Upper bound on | >| init_val_max | | | value for B0 in | >| | | | low-rank | >| | | | update. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_REAL | 0.000 | Lower bound on | >| init_val_min | | | value for B0 in | >| | | | low-rank | >| | | | update. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_STRING | scalar1 | Initialization | >| initialization | | | strategy for | >| | | | the limited | >| | | | memory quasi- | >| | | | Newton | >| | | | approximation. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_INTEGER | 6 | Maximum size of | >| max_history | | | the history for | >| | | | the limited | >| | | | quasi-Newton | >| | | | Hessian | >| | | | approximation. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_INTEGER | 2 | Threshold for | >| max_skipping | | | successive | >| | | | iterations | >| | | | where update is | >| | | | skipped. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_STRING | no | Determines if | >| special_for_res | | | the quasi- | >| to | | | Newton updates | >| | | | should be | >| | | | special during | >| | | | the restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| limited_memory_ | OT_STRING | bfgs | Quasi-Newton | >| update_type | | | update formula | >| | | | for the limited | >| | | | memory | >| | | | approximation. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| line_search_met | OT_STRING | filter | Globalization | >| hod | | | method used in | >| | | | backtracking | >| | | | line search | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_scaling_ | OT_STRING | yes | Flag indicating | >| on_demand | | | that linear | >| | | | scaling is only | >| | | | done if it | >| | | | seems required. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_solver | OT_STRING | mumps | Linear solver | >| | | | used for step | >| | | | computations. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| linear_system_s | OT_STRING | none | Method for | >| caling | | | scaling the | >| | | | linear system. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma27_ignore_sin | OT_STRING | no | Enables MA27's | >| gularity | | | ability to | >| | | | solve a linear | >| | | | system even if | >| | | | the matrix is | >| | | | singular. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma27_la_init_fa | OT_REAL | 5 | Real workspace | >| ctor | | | memory for | >| | | | MA27. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma27_liw_init_f | OT_REAL | 5 | Integer | >| actor | | | workspace | >| | | | memory for | >| | | | MA27. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma27_meminc_fac | OT_REAL | 2 | Increment | >| tor | | | factor for | >| | | | workspace size | >| | | | for MA27. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma27_pivtol | OT_REAL | 0.000 | Pivot tolerance | >| | | | for the linear | >| | | | solver MA27. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma27_pivtolmax | OT_REAL | 0.000 | Maximum pivot | >| | | | tolerance for | >| | | | the linear | >| | | | solver MA27. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma27_skip_inert | OT_STRING | no | Always pretend | >| ia_check | | | inertia is | >| | | | correct. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma28_pivtol | OT_REAL | 0.010 | Pivot tolerance | >| | | | for linear | >| | | | solver MA28. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_automatic_ | OT_STRING | no | Controls MA57 | >| scaling | | | automatic | >| | | | scaling (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_block_size | OT_INTEGER | 16 | Controls block | >| | | | size used by | >| | | | Level 3 BLAS in | >| | | | MA57BD (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_node_amalg | OT_INTEGER | 16 | Node | >| amation | | | amalgamation | >| | | | parameter (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_pivot_orde | OT_INTEGER | 5 | Controls pivot | >| r | | | order in MA57 | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_pivtol | OT_REAL | 0.000 | Pivot tolerance | >| | | | for the linear | >| | | | solver MA57. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_pivtolmax | OT_REAL | 0.000 | Maximum pivot | >| | | | tolerance for | >| | | | the linear | >| | | | solver MA57. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_pre_alloc | OT_REAL | 1.050 | Safety factor | >| | | | for work space | >| | | | memory | >| | | | allocation for | >| | | | the linear | >| | | | solver MA57. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma57_small_pivo | OT_INTEGER | 0 | If set to 1, | >| t_flag | | | then when small | >| | | | entries defined | >| | | | by CNTL(2) are | >| | | | detected they | >| | | | are removed and | >| | | | the | >| | | | corresponding | >| | | | pivots placed | >| | | | at the end of | >| | | | the | >| | | | factorization. | >| | | | This can be | >| | | | particularly | >| | | | efficient if | >| | | | the matrix is | >| | | | highly rank | >| | | | deficient. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_buffer_lpa | OT_INTEGER | 4096 | Number of | >| ge | | | scalars per | >| | | | MA77 buffer | >| | | | page (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_buffer_npa | OT_INTEGER | 1600 | Number of pages | >| ge | | | that make up | >| | | | MA77 buffer | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_file_size | OT_INTEGER | 2097152 | Target size of | >| | | | each temporary | >| | | | file for MA77, | >| | | | scalars per | >| | | | type (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_maxstore | OT_INTEGER | 0 | Maximum storage | >| | | | size for MA77 | >| | | | in-core mode | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_nemin | OT_INTEGER | 8 | Node | >| | | | Amalgamation | >| | | | parameter (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_order | OT_STRING | amd | Controls type | >| | | | of ordering | >| | | | used by | >| | | | HSL_MA77 (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_print_leve | OT_INTEGER | -1 | Debug printing | >| l | | | level for the | >| | | | linear solver | >| | | | MA77 (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_small | OT_REAL | 0.000 | Zero Pivot | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_static | OT_REAL | 0 | Static Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_u | OT_REAL | 0.000 | Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma77_umax | OT_REAL | 0.000 | Maximum | >| | | | Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_nemin | OT_INTEGER | 32 | Node | >| | | | Amalgamation | >| | | | parameter (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_order | OT_STRING | amd | Controls type | >| | | | of ordering | >| | | | used by | >| | | | HSL_MA86 (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_print_leve | OT_INTEGER | -1 | Debug printing | >| l | | | level for the | >| | | | linear solver | >| | | | MA86 (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_scaling | OT_STRING | mc64 | Controls | >| | | | scaling of | >| | | | matrix (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_small | OT_REAL | 0.000 | Zero Pivot | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_static | OT_REAL | 0 | Static Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_u | OT_REAL | 0.000 | Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma86_umax | OT_REAL | 0.000 | Maximum | >| | | | Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_nemin | OT_INTEGER | 8 | Node | >| | | | Amalgamation | >| | | | parameter (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_order | OT_STRING | auto | Controls type | >| | | | of ordering | >| | | | used by | >| | | | HSL_MA97 (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_print_leve | OT_INTEGER | 0 | Debug printing | >| l | | | level for the | >| | | | linear solver | >| | | | MA97 (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_scaling | OT_STRING | dynamic | Specifies | >| | | | strategy for | >| | | | scaling in | >| | | | HSL_MA97 linear | >| | | | solver (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_scaling1 | OT_STRING | mc64 | First scaling. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_scaling2 | OT_STRING | mc64 | Second scaling. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_scaling3 | OT_STRING | mc64 | Third scaling. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_small | OT_REAL | 0.000 | Zero Pivot | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_solve_blas | OT_STRING | no | Controls if | >| 3 | | | blas2 or blas3 | >| | | | routines are | >| | | | used for solve | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_switch1 | OT_STRING | od_hd_reuse | First switch, | >| | | | determine when | >| | | | ma97_scaling1 | >| | | | is enabled. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_switch2 | OT_STRING | never | Second switch, | >| | | | determine when | >| | | | ma97_scaling2 | >| | | | is enabled. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_switch3 | OT_STRING | never | Third switch, | >| | | | determine when | >| | | | ma97_scaling3 | >| | | | is enabled. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_u | OT_REAL | 0.000 | Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| ma97_umax | OT_REAL | 0.000 | Maximum | >| | | | Pivoting | >| | | | Threshold (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| magic_steps | OT_STRING | no | Enables magic | >| | | | steps. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_cpu_time | OT_REAL | 1000000 | Maximum number | >| | | | of CPU seconds. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_filter_rese | OT_INTEGER | 5 | Maximal allowed | >| ts | | | number of | >| | | | filter resets | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_hessian_per | OT_REAL | 1.000e+20 | Maximum value | >| turbation | | | of | >| | | | regularization | >| | | | parameter for | >| | | | handling | >| | | | negative | >| | | | curvature. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter | OT_INTEGER | 3000 | Maximum number | >| | | | of iterations. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_refinement_ | OT_INTEGER | 10 | Maximum number | >| steps | | | of iterative | >| | | | refinement | >| | | | steps per | >| | | | linear system | >| | | | solve. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_resto_iter | OT_INTEGER | 3000000 | Maximum number | >| | | | of successive | >| | | | iterations in | >| | | | restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_soc | OT_INTEGER | 4 | Maximum number | >| | | | of second order | >| | | | correction | >| | | | trial steps at | >| | | | each iteration. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| max_soft_resto_ | OT_INTEGER | 10 | Maximum number | >| iters | | | of iterations | >| | | | performed | >| | | | successively in | >| | | | soft | >| | | | restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mehrotra_algori | OT_STRING | no | Indicates if we | >| thm | | | want to do | >| | | | Mehrotra's | >| | | | algorithm. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| min_alpha_prima | OT_REAL | 0.000 | LIFENG WRITES | >| l | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| min_hessian_per | OT_REAL | 0.000 | Smallest | >| turbation | | | perturbation of | >| | | | the Hessian | >| | | | block. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| min_refinement_ | OT_INTEGER | 1 | Minimum number | >| steps | | | of iterative | >| | | | refinement | >| | | | steps per | >| | | | linear system | >| | | | solve. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_allow_fast_m | OT_STRING | yes | Allow skipping | >| onotone_decreas | | | of barrier | >| e | | | problem if | >| | | | barrier test is | >| | | | already met. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_init | OT_REAL | 0.100 | Initial value | >| | | | for the barrier | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_linear_decre | OT_REAL | 0.200 | Determines | >| ase_factor | | | linear decrease | >| | | | rate of barrier | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_max | OT_REAL | 100000 | Maximum value | >| | | | for barrier | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_max_fact | OT_REAL | 1000 | Factor for | >| | | | initialization | >| | | | of maximum | >| | | | value for | >| | | | barrier | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_min | OT_REAL | 0.000 | Minimum value | >| | | | for barrier | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_oracle | OT_STRING | quality- | Oracle for a | >| | | function | new barrier | >| | | | parameter in | >| | | | the adaptive | >| | | | strategy. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_strategy | OT_STRING | monotone | Update strategy | >| | | | for barrier | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_superlinear_ | OT_REAL | 1.500 | Determines | >| decrease_power | | | superlinear | >| | | | decrease rate | >| | | | of barrier | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mu_target | OT_REAL | 0 | Desired value | >| | | | of complementar | >| | | | ity. (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mult_diverg_fea | OT_REAL | 0.000 | tolerance for | >| sibility_tol | | | deciding if the | >| | | | multipliers are | >| | | | diverging (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mult_diverg_y_t | OT_REAL | 100000000 | tolerance for | >| ol | | | deciding if the | >| | | | multipliers are | >| | | | diverging (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mumps_dep_tol | OT_REAL | 0 | Pivot threshold | >| | | | for detection | >| | | | of linearly | >| | | | dependent | >| | | | constraints in | >| | | | MUMPS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mumps_mem_perce | OT_INTEGER | 1000 | Percentage | >| nt | | | increase in the | >| | | | estimated | >| | | | working space | >| | | | for MUMPS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mumps_permuting | OT_INTEGER | 7 | Controls | >| _scaling | | | permuting and | >| | | | scaling in | >| | | | MUMPS (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mumps_pivot_ord | OT_INTEGER | 7 | Controls pivot | >| er | | | order in MUMPS | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mumps_pivtol | OT_REAL | 0.000 | Pivot tolerance | >| | | | for the linear | >| | | | solver MUMPS. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mumps_pivtolmax | OT_REAL | 0.100 | Maximum pivot | >| | | | tolerance for | >| | | | the linear | >| | | | solver MUMPS. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| mumps_scaling | OT_INTEGER | 77 | Controls | >| | | | scaling in | >| | | | MUMPS (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| neg_curv_test_t | OT_REAL | 0 | Tolerance for | >| ol | | | heuristic to | >| | | | ignore wrong | >| | | | inertia. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| never_use_fact_ | OT_STRING | no | Toggle to | >| cgpen_direction | | | switch off the | >| | | | fast Chen- | >| | | | Goldfarb | >| | | | direction (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| never_use_piece | OT_STRING | no | Toggle to | >| wise_penalty_ls | | | switch off the | >| | | | piecewise | >| | | | penalty method | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_lower_bound | OT_REAL | -1.000e+19 | any bound less | >| _inf | | | or equal this | >| | | | value will be | >| | | | considered -inf | >| | | | (i.e. not lower | >| | | | bounded). (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_scaling_con | OT_REAL | 0 | Target value | >| str_target_grad | | | for constraint | >| ient | | | function | >| | | | gradient size. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_scaling_max | OT_REAL | 100 | Maximum | >| _gradient | | | gradient after | >| | | | NLP scaling. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_scaling_met | OT_STRING | gradient-based | Select the | >| hod | | | technique used | >| | | | for scaling the | >| | | | NLP. (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_scaling_min | OT_REAL | 0.000 | Minimum value | >| _value | | | of gradient- | >| | | | based scaling | >| | | | values. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_scaling_obj | OT_REAL | 0 | Target value | >| _target_gradien | | | for objective | >| t | | | function | >| | | | gradient size. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_upper_bound | OT_REAL | 1.000e+19 | any bound | >| _inf | | | greater or this | >| | | | value will be | >| | | | considered +inf | >| | | | (i.e. not upper | >| | | | bounded). (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nu_inc | OT_REAL | 0.000 | Increment of | >| | | | the penalty | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| nu_init | OT_REAL | 0.000 | Initial value | >| | | | of the penalty | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| num_linear_vari | OT_INTEGER | 0 | Number of | >| ables | | | linear | >| | | | variables (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| obj_max_inc | OT_REAL | 5 | Determines the | >| | | | upper bound on | >| | | | the acceptable | >| | | | increase of | >| | | | barrier | >| | | | objective | >| | | | function. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| obj_scaling_fac | OT_REAL | 1 | Scaling factor | >| tor | | | for the | >| | | | objective | >| | | | function. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| option_file_nam | OT_STRING | ipopt.opt | File name of | >| e | | | options file. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| output_file | OT_STRING | | File name of | >| | | | desired output | >| | | | file (leave | >| | | | unset for no | >| | | | file output). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iter_co | OT_INTEGER | 5000 | Maximum Size of | >| arse_size | | | Coarse Grid | >| | | | Matrix (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iter_dr | OT_REAL | 0.500 | dropping value | >| opping_factor | | | for incomplete | >| | | | factor (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iter_dr | OT_REAL | 0.100 | dropping value | >| opping_schur | | | for sparsify | >| | | | schur | >| | | | complement | >| | | | factor (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iter_in | OT_REAL | 5000000 | (see IPOPT | >| verse_norm_fact | | | documentation) | >| or | | | | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iter_ma | OT_INTEGER | 10 | Maximum Size of | >| x_levels | | | Grid Levels | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iter_ma | OT_INTEGER | 10000000 | max fill for | >| x_row_fill | | | each row (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iter_re | OT_REAL | 0.000 | Relative | >| lative_tol | | | Residual | >| | | | Convergence | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_iterati | OT_STRING | no | Switch on | >| ve | | | iterative | >| | | | solver in | >| | | | Pardiso library | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_matchin | OT_STRING | complete+2x2 | Matching | >| g_strategy | | | strategy to be | >| | | | used by Pardiso | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_max_dro | OT_INTEGER | 4 | Maximal number | >| ptol_correction | | | of decreases of | >| s | | | drop tolerance | >| | | | during one | >| | | | solve. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_max_ite | OT_INTEGER | 500 | Maximum number | >| r | | | of Krylov- | >| | | | Subspace | >| | | | Iteration (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_msglvl | OT_INTEGER | 0 | Pardiso message | >| | | | level (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_out_of_ | OT_INTEGER | 0 | Enables out-of- | >| core_power | | | core variant of | >| | | | Pardiso (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_redo_sy | OT_STRING | no | Toggle for | >| mbolic_fact_onl | | | handling case | >| y_if_inertia_wr | | | when elements | >| ong | | | were perturbed | >| | | | by Pardiso. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_repeate | OT_STRING | no | Interpretation | >| d_perturbation_ | | | of perturbed | >| means_singular | | | elements. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pardiso_skip_in | OT_STRING | no | Always pretend | >| ertia_check | | | inertia is | >| | | | correct. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pass_nonlinear_ | OT_BOOLEAN | False | n/a | >| variables | | | | >+-----------------+-----------------+-----------------+-----------------+ >| pen_des_fact | OT_REAL | 0.200 | a parameter | >| | | | used in penalty | >| | | | parameter | >| | | | computation | >| | | | (for Chen- | >| | | | Goldfarb line | >| | | | search). (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pen_init_fac | OT_REAL | 50 | a parameter | >| | | | used to choose | >| | | | initial penalty | >| | | | parameterswhen | >| | | | the regularized | >| | | | Newton method | >| | | | is used. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| pen_theta_max_f | OT_REAL | 10000 | Determines | >| act | | | upper bound for | >| | | | constraint | >| | | | violation in | >| | | | the filter. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| penalty_init_ma | OT_REAL | 100000 | Maximal value | >| x | | | for the intial | >| | | | penalty | >| | | | parameter (for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| penalty_init_mi | OT_REAL | 1 | Minimal value | >| n | | | for the intial | >| | | | penalty | >| | | | parameter for | >| | | | line search(for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| penalty_max | OT_REAL | 1.000e+30 | Maximal value | >| | | | for the penalty | >| | | | parameter (for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| penalty_update_ | OT_REAL | 10 | LIFENG WRITES | >| compl_tol | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| penalty_update_ | OT_REAL | 0.000 | Threshold for | >| infeasibility_t | | | infeasibility | >| ol | | | in penalty | >| | | | parameter | >| | | | update test. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| perturb_always_ | OT_STRING | no | Active | >| cd | | | permanent | >| | | | perturbation of | >| | | | constraint | >| | | | linearization. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| perturb_dec_fac | OT_REAL | 0.333 | Decrease factor | >| t | | | for x-s | >| | | | perturbation. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| perturb_inc_fac | OT_REAL | 8 | Increase factor | >| t | | | for x-s | >| | | | perturbation. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| perturb_inc_fac | OT_REAL | 100 | Increase factor | >| t_first | | | for x-s | >| | | | perturbation | >| | | | for very first | >| | | | perturbation. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| piecewisepenalt | OT_REAL | 0.000 | LIFENG WRITES | >| y_gamma_infeasi | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| piecewisepenalt | OT_REAL | 0.000 | LIFENG WRITES | >| y_gamma_obj | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| point_perturbat | OT_REAL | 10 | Maximal | >| ion_radius | | | perturbation of | >| | | | an evaluation | >| | | | point. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_frequency | OT_INTEGER | 1 | Determines at | >| _iter | | | which iteration | >| | | | frequency the | >| | | | summarizing | >| | | | iteration | >| | | | output line | >| | | | should be | >| | | | printed. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_frequency | OT_REAL | 0 | Determines at | >| _time | | | which time | >| | | | frequency the | >| | | | summarizing | >| | | | iteration | >| | | | output line | >| | | | should be | >| | | | printed. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_info_stri | OT_STRING | no | Enables | >| ng | | | printing of | >| | | | additional info | >| | | | string at end | >| | | | of iteration | >| | | | output. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_level | OT_INTEGER | 5 | Output | >| | | | verbosity | >| | | | level. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_options_d | OT_STRING | no | Switch to print | >| ocumentation | | | all algorithmic | >| | | | options. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_options_l | OT_STRING | no | Undocumented | >| atex_mode | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_time | OT_BOOLEAN | True | print | >| | | | information | >| | | | about execution | >| | | | time | >+-----------------+-----------------+-----------------+-----------------+ >| print_timing_st | OT_STRING | no | Switch to print | >| atistics | | | timing | >| | | | statistics. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| print_user_opti | OT_STRING | no | Print all | >| ons | | | options set by | >| | | | the user. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| quality_functio | OT_STRING | none | The balancing | >| n_balancing_ter | | | term included | >| m | | | in the quality | >| | | | function for | >| | | | centrality. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| quality_functio | OT_STRING | none | The penalty | >| n_centrality | | | term for | >| | | | centrality that | >| | | | is included in | >| | | | quality | >| | | | function. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| quality_functio | OT_INTEGER | 8 | Maximum number | >| n_max_section_s | | | of search steps | >| teps | | | during direct | >| | | | search | >| | | | procedure | >| | | | determining the | >| | | | optimal | >| | | | centering | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| quality_functio | OT_STRING | 2-norm-squared | Norm used for | >| n_norm_type | | | components of | >| | | | the quality | >| | | | function. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| quality_functio | OT_REAL | 0 | Tolerance for | >| n_section_qf_to | | | the golden | >| l | | | section search | >| | | | procedure | >| | | | determining the | >| | | | optimal | >| | | | centering | >| | | | parameter (in | >| | | | the function | >| | | | value space). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| quality_functio | OT_REAL | 0.010 | Tolerance for | >| n_section_sigma | | | the section | >| _tol | | | search | >| | | | procedure | >| | | | determining the | >| | | | optimal | >| | | | centering | >| | | | parameter (in | >| | | | sigma space). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| recalc_y | OT_STRING | no | Tells the | >| | | | algorithm to | >| | | | recalculate the | >| | | | equality and | >| | | | inequality | >| | | | multipliers as | >| | | | least square | >| | | | estimates. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| recalc_y_feas_t | OT_REAL | 0.000 | Feasibility | >| ol | | | threshold for | >| | | | recomputation | >| | | | of multipliers. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| replace_bounds | OT_STRING | no | Indicates if | >| | | | all variable | >| | | | bounds should | >| | | | be replaced by | >| | | | inequality | >| | | | constraints | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| required_infeas | OT_REAL | 0.900 | Required | >| ibility_reducti | | | reduction of | >| on | | | infeasibility | >| | | | before leaving | >| | | | restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| residual_improv | OT_REAL | 1.000 | Minimal | >| ement_factor | | | required | >| | | | reduction of | >| | | | residual test | >| | | | ratio in | >| | | | iterative | >| | | | refinement. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| residual_ratio_ | OT_REAL | 0.000 | Iterative | >| max | | | refinement | >| | | | tolerance (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| residual_ratio_ | OT_REAL | 0.000 | Threshold for | >| singular | | | declaring | >| | | | linear system | >| | | | singular after | >| | | | failed | >| | | | iterative | >| | | | refinement. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| resto_failure_f | OT_REAL | 0 | Threshold for | >| easibility_thre | | | primal | >| shold | | | infeasibility | >| | | | to declare | >| | | | failure of | >| | | | restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| resto_penalty_p | OT_REAL | 1000 | Penalty | >| arameter | | | parameter in | >| | | | the restoration | >| | | | phase objective | >| | | | function. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| resto_proximity | OT_REAL | 1 | Weighting | >| _weight | | | factor for the | >| | | | proximity term | >| | | | in restoration | >| | | | phase | >| | | | objective. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| rho | OT_REAL | 0.100 | Value in | >| | | | penalty | >| | | | parameter | >| | | | update formula. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| s_max | OT_REAL | 100 | Scaling | >| | | | threshold for | >| | | | the NLP error. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| s_phi | OT_REAL | 2.300 | Exponent for | >| | | | linear barrier | >| | | | function model | >| | | | in the | >| | | | switching rule. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| s_theta | OT_REAL | 1.100 | Exponent for | >| | | | current | >| | | | constraint | >| | | | violation in | >| | | | the switching | >| | | | rule. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| sb | OT_STRING | no | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| sigma_max | OT_REAL | 100 | Maximum value | >| | | | of the | >| | | | centering | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| sigma_min | OT_REAL | 0.000 | Minimum value | >| | | | of the | >| | | | centering | >| | | | parameter. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| skip_corr_if_ne | OT_STRING | yes | Skip the | >| g_curv | | | corrector step | >| | | | in negative | >| | | | curvature | >| | | | iteration | >| | | | (unsupported!). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| skip_corr_in_mo | OT_STRING | yes | Skip the | >| notone_mode | | | corrector step | >| | | | during monotone | >| | | | barrier | >| | | | parameter mode | >| | | | (unsupported!). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| skip_finalize_s | OT_STRING | no | Indicates if | >| olution_call | | | call to NLP::Fi | >| | | | nalizeSolution | >| | | | after | >| | | | optimization | >| | | | should be | >| | | | suppressed (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| slack_bound_fra | OT_REAL | 0.010 | Desired minimum | >| c | | | relative | >| | | | distance from | >| | | | the initial | >| | | | slack to bound. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| slack_bound_pus | OT_REAL | 0.010 | Desired minimum | >| h | | | absolute | >| | | | distance from | >| | | | the initial | >| | | | slack to bound. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| slack_move | OT_REAL | 0.000 | Correction size | >| | | | for very small | >| | | | slacks. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| soft_resto_pder | OT_REAL | 1.000 | Required | >| ror_reduction_f | | | reduction in | >| actor | | | primal-dual | >| | | | error in the | >| | | | soft | >| | | | restoration | >| | | | phase. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| start_with_rest | OT_STRING | no | Tells algorithm | >| o | | | to switch to | >| | | | restoration | >| | | | phase in first | >| | | | iteration. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| suppress_all_ou | OT_STRING | no | Undocumented | >| tput | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| tau_min | OT_REAL | 0.990 | Lower bound on | >| | | | fraction-to- | >| | | | the-boundary | >| | | | parameter tau. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| theta_max_fact | OT_REAL | 10000 | Determines | >| | | | upper bound for | >| | | | constraint | >| | | | violation in | >| | | | the filter. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| theta_min | OT_REAL | 0.000 | LIFENG WRITES | >| | | | THIS. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| theta_min_fact | OT_REAL | 0.000 | Determines | >| | | | constraint | >| | | | violation | >| | | | threshold in | >| | | | the switching | >| | | | rule. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| tiny_step_tol | OT_REAL | 0.000 | Tolerance for | >| | | | detecting | >| | | | numerically | >| | | | insignificant | >| | | | steps. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| tiny_step_y_tol | OT_REAL | 0.010 | Tolerance for | >| | | | quitting | >| | | | because of | >| | | | numerically | >| | | | insignificant | >| | | | steps. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| tol | OT_REAL | 0.000 | Desired | >| | | | convergence | >| | | | tolerance | >| | | | (relative). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| var_integer_md | OT_DICTIONARY | None | Integer | >| | | | metadata (a | >| | | | dictionary with | >| | | | lists of | >| | | | integers) about | >| | | | variables to be | >| | | | passed to IPOPT | >+-----------------+-----------------+-----------------+-----------------+ >| var_numeric_md | OT_DICTIONARY | None | Numeric | >| | | | metadata (a | >| | | | dictionary with | >| | | | lists of reals) | >| | | | about variables | >| | | | to be passed to | >| | | | IPOPT | >+-----------------+-----------------+-----------------+-----------------+ >| var_string_md | OT_DICTIONARY | None | String metadata | >| | | | (a dictionary | >| | | | with lists of | >| | | | strings) about | >| | | | variables to be | >| | | | passed to IPOPT | >+-----------------+-----------------+-----------------+-----------------+ >| vartheta | OT_REAL | 0.500 | a parameter | >| | | | used to check | >| | | | if the fast | >| | | | direction can | >| | | | be used asthe | >| | | | line search | >| | | | direction (for | >| | | | Chen-Goldfarb | >| | | | line search). | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_boun | OT_REAL | 0.001 | same as | >| d_frac | | | bound_frac for | >| | | | the regular | >| | | | initializer. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_boun | OT_REAL | 0.001 | same as | >| d_push | | | bound_push for | >| | | | the regular | >| | | | initializer. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_enti | OT_STRING | no | Tells algorithm | >| re_iterate | | | whether to use | >| | | | the GetWarmStar | >| | | | tIterate method | >| | | | in the NLP. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_init | OT_STRING | no | Warm-start for | >| _point | | | initial point | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_mult | OT_REAL | 0.001 | same as | >| _bound_push | | | mult_bound_push | >| | | | for the regular | >| | | | initializer. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_mult | OT_REAL | 1000000 | Maximum initial | >| _init_max | | | value for the | >| | | | equality | >| | | | multipliers. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_same | OT_STRING | no | Indicates | >| _structure | | | whether a | >| | | | problem with a | >| | | | structure | >| | | | identical to | >| | | | the previous | >| | | | one is to be | >| | | | solved. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_slac | OT_REAL | 0.001 | same as slack_b | >| k_bound_frac | | | ound_frac for | >| | | | the regular | >| | | | initializer. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_slac | OT_REAL | 0.001 | same as slack_b | >| k_bound_push | | | ound_push for | >| | | | the regular | >| | | | initializer. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start_targ | OT_REAL | 0 | Unsupported! | >| et_mu | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| watchdog_shorte | OT_INTEGER | 10 | Number of | >| ned_iter_trigge | | | shortened | >| r | | | iterations that | >| | | | trigger the | >| | | | watchdog. (see | >| | | | IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| watchdog_trial_ | OT_INTEGER | 3 | Maximum number | >| iter_max | | | of watchdog | >| | | | iterations. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ >| wsmp_iterative | OT_STRING | no | Switches to | >| | | | iterative | >| | | | solver in WSMP. | >| | | | (see IPOPT | >| | | | documentation) | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-------------+ >| Id | >+=============+ >| eval_f | >+-------------+ >| eval_g | >+-------------+ >| eval_grad_f | >+-------------+ >| eval_h | >+-------------+ >| eval_jac_g | >+-------------+ > >>List of available stats > >+--------------------+ >| Id | >+====================+ >| con_integer_md | >+--------------------+ >| con_numeric_md | >+--------------------+ >| con_string_md | >+--------------------+ >| iter_count | >+--------------------+ >| iteration | >+--------------------+ >| iterations | >+--------------------+ >| n_eval_f | >+--------------------+ >| n_eval_g | >+--------------------+ >| n_eval_grad_f | >+--------------------+ >| n_eval_h | >+--------------------+ >| n_eval_jac_g | >+--------------------+ >| return_status | >+--------------------+ >| t_callback_fun | >+--------------------+ >| t_callback_prepare | >+--------------------+ >| t_eval_f | >+--------------------+ >| t_eval_g | >+--------------------+ >| t_eval_grad_f | >+--------------------+ >| t_eval_h | >+--------------------+ >| t_eval_jac_g | >+--------------------+ >| t_mainloop | >+--------------------+ >| var_integer_md | >+--------------------+ >| var_numeric_md | >+--------------------+ >| var_string_md | >+--------------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >knitro >------ > > > >KNITRO interface > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| BarRule | OT_INTEGER | 0 | Barrier Rule | >+-----------------+-----------------+-----------------+-----------------+ >| Debug | OT_INTEGER | 0 | Debug level | >+-----------------+-----------------+-----------------+-----------------+ >| Delta | OT_REAL | 1 | Initial region | >| | | | scaling factor | >+-----------------+-----------------+-----------------+-----------------+ >| FeasModeTol | OT_REAL | 0.000 | Feasible mode | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| FeasTol | OT_REAL | 0.000 | Feasible | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| FeasTolAbs | OT_REAL | 1 | Absolute | >| | | | feasible | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| Feasible | OT_BOOLEAN | 0 | Allow | >| | | | infeasible | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| GradOpt | OT_INTEGER | 1 | Gradient | >| | | | calculation | >| | | | method | >+-----------------+-----------------+-----------------+-----------------+ >| HessOpt | OT_INTEGER | 1 | Hessian | >| | | | calculation | >| | | | method | >+-----------------+-----------------+-----------------+-----------------+ >| HonorBnds | OT_BOOLEAN | 0 | Enforce bounds | >+-----------------+-----------------+-----------------+-----------------+ >| InitPt | OT_BOOLEAN | 0 | Use initial | >| | | | point strategy | >+-----------------+-----------------+-----------------+-----------------+ >| LmSize | OT_INTEGER | 10 | Memory pairsize | >| | | | limit | >+-----------------+-----------------+-----------------+-----------------+ >| LpSolver | OT_BOOLEAN | 0 | Use LpSolver | >+-----------------+-----------------+-----------------+-----------------+ >| MaxCgIt | OT_INTEGER | 0 | Maximum | >| | | | conjugate | >| | | | gradient | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| MaxIt | OT_INTEGER | 10000 | Iteration limit | >+-----------------+-----------------+-----------------+-----------------+ >| Mu | OT_REAL | 0.100 | Initial barrier | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| Multistart | OT_BOOLEAN | 0 | Use multistart | >+-----------------+-----------------+-----------------+-----------------+ >| NewPoint | OT_BOOLEAN | 0 | Select new- | >| | | | point feature | >+-----------------+-----------------+-----------------+-----------------+ >| ObjRange | OT_REAL | 0.000 | Maximum | >| | | | objective value | >+-----------------+-----------------+-----------------+-----------------+ >| OptTol | OT_REAL | 0.000 | Relative | >| | | | optimality | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| OptTolAbs | OT_REAL | 0 | Absolute | >| | | | optimality | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| OutLev | OT_INTEGER | 2 | Log output | >| | | | level | >+-----------------+-----------------+-----------------+-----------------+ >| Pivot | OT_REAL | 0.000 | Initial pivot | >| | | | threshold | >+-----------------+-----------------+-----------------+-----------------+ >| Scale | OT_BOOLEAN | 1 | Perform scaling | >+-----------------+-----------------+-----------------+-----------------+ >| ShiftInit | OT_BOOLEAN | 1 | Interior-point | >| | | | shifting | >| | | | initial point | >+-----------------+-----------------+-----------------+-----------------+ >| Soc | OT_INTEGER | 1 | Second order | >| | | | correction | >+-----------------+-----------------+-----------------+-----------------+ >| XTol | OT_REAL | 0.000 | Relative | >| | | | solution change | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| contype | OT_INTEGERVECTO | | | >| | R | | | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-------------+ >| Id | >+=============+ >| eval_f | >+-------------+ >| eval_g | >+-------------+ >| eval_grad_f | >+-------------+ >| eval_h | >+-------------+ >| eval_jac_g | >+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >snopt >----- > > > >SNOPT interface > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| _feasibility_to | OT_REAL | None | Feasibility | >| lerance | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| _iprint | OT_INTEGER | 0 | n/a | >+-----------------+-----------------+-----------------+-----------------+ >| _isumm | OT_INTEGER | 6 | n/a | >+-----------------+-----------------+-----------------+-----------------+ >| _major_iteratio | OT_INTEGER | None | Major iteration | >| n_limit | | | limit | >+-----------------+-----------------+-----------------+-----------------+ >| _minor_iteratio | OT_INTEGER | None | Minor iteration | >| n_limit | | | limit | >+-----------------+-----------------+-----------------+-----------------+ >| _optimality_tol | OT_REAL | None | Optimality | >| erance | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| _scale_option | OT_INTEGER | None | Scale option | >+-----------------+-----------------+-----------------+-----------------+ >| _start | OT_STRING | Cold | | >+-----------------+-----------------+-----------------+-----------------+ >| _verify_level | OT_INTEGER | None | Verify level | >+-----------------+-----------------+-----------------+-----------------+ >| detect_linear | OT_BOOLEAN | True | Make an effort | >| | | | to treat linear | >| | | | constraints and | >| | | | linear | >| | | | variables | >| | | | specially. | >+-----------------+-----------------+-----------------+-----------------+ >| print_time | OT_BOOLEAN | True | print | >| | | | information | >| | | | about execution | >| | | | time | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-----------+ >| Id | >+===========+ >| eval_nlp | >+-----------+ >| setup_nlp | >+-----------+ > >>List of available stats > >+----------------+ >| Id | >+================+ >| iter_count | >+----------------+ >| iterations | >+----------------+ >| n_callback_fun | >+----------------+ >| n_eval_grad_f | >+----------------+ >| n_eval_jac_g | >+----------------+ >| return_status | >+----------------+ >| t_callback_fun | >+----------------+ >| t_eval_grad_f | >+----------------+ >| t_eval_jac_g | >+----------------+ >| t_mainloop | >+----------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >worhp >----- > > > >WORHP interface > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| AcceptTolFeas | OT_REAL | 0.001 | Tolerance for | >| | | | acceptable | >| | | | feasibility | >+-----------------+-----------------+-----------------+-----------------+ >| AcceptTolOpti | OT_REAL | 0.001 | Tolerance for | >| | | | acceptable | >| | | | optimality | >+-----------------+-----------------+-----------------+-----------------+ >| AlphaMinConst | OT_BOOLEAN | False | Use a constant | >| | | | lower bound on | >| | | | Armijo stepsize | >| | | | in Filter | >+-----------------+-----------------+-----------------+-----------------+ >| Ares | OT_INTEGERVECTO | [42, 41, 42, | Armijo recovery | >| | R | 43, 44, 41, 50] | strategies. | >| | | | Vector of size | >| | | | 7 | >+-----------------+-----------------+-----------------+-----------------+ >| ArmijoBeta | OT_REAL | 0.712 | Trial stepsize | >| | | | decrease factor | >| | | | for Armijo rule | >+-----------------+-----------------+-----------------+-----------------+ >| ArmijoMaxAlpha | OT_REAL | 1 | Initial alpha | >| | | | for Armijo rule | >+-----------------+-----------------+-----------------+-----------------+ >| ArmijoMinAlpha | OT_REAL | 0.000 | Lower bound on | >| | | | alpha for | >| | | | Armijo rule | >+-----------------+-----------------+-----------------+-----------------+ >| ArmijoMinAlphaR | OT_REAL | 0.000 | Lower bound on | >| ec | | | alpha for | >| | | | Armijo rule | >| | | | during recovery | >+-----------------+-----------------+-----------------+-----------------+ >| ArmijoSigma | OT_REAL | 0.005 | Scale factor | >| | | | for linearised | >| | | | descent check | >| | | | in Armijo rule | >+-----------------+-----------------+-----------------+-----------------+ >| AutoQPRecovery | OT_BOOLEAN | True | Enable | >| | | | automatic QP | >| | | | recovery | >+-----------------+-----------------+-----------------+-----------------+ >| BFGSmaxblockSiz | OT_INTEGER | 300 | Block size | >| e | | | parameter used | >| | | | by certain BFGS | >| | | | methods | >+-----------------+-----------------+-----------------+-----------------+ >| BFGSmethod | OT_INTEGER | 0 | Choose BFGS | >| | | | method (0: | >| | | | dense, 1-3: | >| | | | block, 100+: | >| | | | sparse) | >+-----------------+-----------------+-----------------+-----------------+ >| BFGSminblockSiz | OT_INTEGER | 300 | Block size | >| e | | | parameter used | >| | | | by certain BFGS | >| | | | methods | >+-----------------+-----------------+-----------------+-----------------+ >| BFGSrestart | OT_INTEGER | 50 | Restart BFGS | >| | | | update after | >| | | | this many | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| BettsFactor | OT_REAL | 2.100 | Update factor | >| | | | for Betts' | >| | | | Hessian | >| | | | regularisation | >+-----------------+-----------------+-----------------+-----------------+ >| BettsPoint | OT_REAL | 1 | Smallest | >| | | | eigenvalue of | >| | | | the regularised | >| | | | Hessian | >+-----------------+-----------------+-----------------+-----------------+ >| BoundTolFac | OT_REAL | 1000 | Factor in | >| | | | determining | >| | | | active | >| | | | constraints by | >| | | | KKT | >+-----------------+-----------------+-----------------+-----------------+ >| CheckFJ | OT_REAL | 1.000e+12 | Upper bound | >| | | | used by Fritz- | >| | | | John heuristic | >+-----------------+-----------------+-----------------+-----------------+ >| CheckStructureD | OT_BOOLEAN | True | Enable | >| F | | | structural | >| | | | checking of DF | >+-----------------+-----------------+-----------------+-----------------+ >| CheckStructureD | OT_BOOLEAN | True | Enable | >| G | | | structural | >| | | | checking of DG | >+-----------------+-----------------+-----------------+-----------------+ >| CheckStructureH | OT_BOOLEAN | True | Enable | >| M | | | structural | >| | | | checking of HM | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepBettsSum | OT_REAL | 0.500 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepConStop | OT_REAL | 0.000 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepConvio | OT_REAL | 1 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepMaxIter | OT_INTEGER | 50 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepMethod | OT_INTEGER | 0 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepMode | OT_INTEGER | 1 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepPFactor | OT_REAL | 1 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepPMax | OT_REAL | 1000000 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| CorStepRecovery | OT_BOOLEAN | False | (experimental) | >| DX | | | | >+-----------------+-----------------+-----------------+-----------------+ >| CurvBCond | OT_REAL | 0.020 | Block BFGS | >| | | | curvature | >| | | | condition bound | >+-----------------+-----------------+-----------------+-----------------+ >| CurvBFac | OT_REAL | 0.300 | Block BFGS | >| | | | curvature | >| | | | condition | >| | | | regularisation | >| | | | factor | >+-----------------+-----------------+-----------------+-----------------+ >| CurvCond | OT_REAL | 0.020 | BFGS Curvature | >| | | | condition bound | >+-----------------+-----------------+-----------------+-----------------+ >| CurvFac | OT_REAL | 0.300 | BFGS curvature | >| | | | condition | >| | | | regularisation | >| | | | factor | >+-----------------+-----------------+-----------------+-----------------+ >| DebugMarker05 | OT_INTEGER | 42 | Debug marker. | >| | | | Used to find | >| | | | memory alignmen | >| | | | t/padding | >| | | | issues | >+-----------------+-----------------+-----------------+-----------------+ >| DebugMarker06 | OT_INTEGER | 42 | Debug marker. | >| | | | Used to find | >| | | | memory alignmen | >| | | | t/padding | >| | | | issues | >+-----------------+-----------------+-----------------+-----------------+ >| FGtogether | OT_BOOLEAN | False | F and G cannot | >| | | | be evaluated | >| | | | separately | >+-----------------+-----------------+-----------------+-----------------+ >| FJandND | OT_BOOLEAN | False | Enable Fritz- | >| | | | John and non- | >| | | | differentiable | >| | | | check | >| | | | heuristics | >+-----------------+-----------------+-----------------+-----------------+ >| FeasibleDual | OT_BOOLEAN | False | Activate dual | >| | | | feasibility | >| | | | mode | >+-----------------+-----------------+-----------------+-----------------+ >| FeasibleInit | OT_BOOLEAN | False | Activate | >| | | | initial | >| | | | feasibility | >| | | | mode | >+-----------------+-----------------+-----------------+-----------------+ >| FeasibleInitTol | OT_REAL | 0.001 | Feasibility | >| | | | tolerance for | >| | | | no-objective | >| | | | feasible mode | >+-----------------+-----------------+-----------------+-----------------+ >| FeasibleOnly | OT_BOOLEAN | False | Activate | >| | | | feasible-only | >| | | | mode | >+-----------------+-----------------+-----------------+-----------------+ >| FidifEps | OT_REAL | 0.000 | Finite | >| | | | difference | >| | | | perturbation | >+-----------------+-----------------+-----------------+-----------------+ >| FidifHM | OT_BOOLEAN | False | Approximate | >| | | | Hessian by | >| | | | finite | >| | | | differences | >| | | | (otherwise | >| | | | BFGS) | >+-----------------+-----------------+-----------------+-----------------+ >| FilterBisecAlph | OT_BOOLEAN | True | Filter | >| a | | | heuristic to | >| | | | save Armijo | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| FilterGammaCV | OT_REAL | 0.000 | Constraint | >| | | | violation | >| | | | decrease factor | >| | | | in Filter | >| | | | acceptance | >| | | | check | >+-----------------+-----------------+-----------------+-----------------+ >| FilterGammaF | OT_REAL | 0.000 | Objective | >| | | | decrease factor | >| | | | in Filter | >| | | | acceptance | >| | | | check | >+-----------------+-----------------+-----------------+-----------------+ >| FilterIntersecA | OT_BOOLEAN | True | Filter | >| lpha | | | heuristic to | >| | | | save Armijo | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| FirstDifCentral | OT_BOOLEAN | True | Use central | >| | | | finite | >| | | | difference | >| | | | quotient for | >| | | | first | >| | | | derivatives | >+-----------------+-----------------+-----------------+-----------------+ >| FocusOnFeas | OT_BOOLEAN | True | Enable Focus- | >| | | | on-Feasibility | >| | | | mode | >+-----------------+-----------------+-----------------+-----------------+ >| FocusOnFeasFact | OT_REAL | 1.360 | Factor in | >| or | | | Focus-on- | >| | | | Feasibility | >| | | | mode | >+-----------------+-----------------+-----------------+-----------------+ >| GammaAlpha | OT_REAL | 0.050 | Safety factor | >| | | | for alphamin | >| | | | calculation by | >| | | | Filter | >+-----------------+-----------------+-----------------+-----------------+ >| GroupMethod | OT_INTEGER | 1 | Select method | >| | | | to determine | >| | | | graph colouring | >| | | | groups | >+-----------------+-----------------+-----------------+-----------------+ >| IgnoreFilterCri | OT_BOOLEAN | False | Activate | >| t | | | accelerating | >| | | | heuristics for | >| | | | Filter | >+-----------------+-----------------+-----------------+-----------------+ >| IncBettsTau | OT_REAL | 2 | Increase factor | >| | | | for Betts' | >| | | | update | >| | | | dampening term | >+-----------------+-----------------+-----------------+-----------------+ >| IncBettsTauMore | OT_REAL | 100 | Larger increase | >| | | | factor for | >| | | | Betts' update | >| | | | dampening term | >+-----------------+-----------------+-----------------+-----------------+ >| IncreaseIWS | OT_REAL | 1 | Increase factor | >| | | | for estimated | >| | | | integer | >| | | | workspace | >| | | | requirement | >+-----------------+-----------------+-----------------+-----------------+ >| IncreaseRWS | OT_REAL | 1 | Increase factor | >| | | | for estimated | >| | | | real workspace | >| | | | requirement | >+-----------------+-----------------+-----------------+-----------------+ >| Infty | OT_REAL | 1.000e+20 | Upper bound for | >| | | | numbers to be | >| | | | regarded as | >| | | | finite | >+-----------------+-----------------+-----------------+-----------------+ >| InftyUnbounded | OT_REAL | 1.000e+20 | Tolerance for | >| | | | unboundedness | >| | | | detection | >| | | | heuristic | >+-----------------+-----------------+-----------------+-----------------+ >| InitialLMest | OT_BOOLEAN | True | Enable initial | >| | | | Lagrange | >| | | | multiplier | >| | | | estimate | >+-----------------+-----------------+-----------------+-----------------+ >| KeepAcceptableS | OT_BOOLEAN | True | Save acceptable | >| ol | | | solutions as | >| | | | fallback | >+-----------------+-----------------+-----------------+-----------------+ >| LMestQPipComTol | OT_REAL | 0.003 | IP | >| | | | complementarity | >| | | | tolerance in | >| | | | initial | >| | | | multiplier | >| | | | estimate | >+-----------------+-----------------+-----------------+-----------------+ >| LMestQPipResTol | OT_REAL | 1 | IP residual | >| | | | tolerance in | >| | | | initial | >| | | | multiplier | >| | | | estimate | >+-----------------+-----------------+-----------------+-----------------+ >| LinMult | OT_BOOLEAN | False | Control | >| | | | Lagrange | >| | | | multiplier | >| | | | update | >+-----------------+-----------------+-----------------+-----------------+ >| LogLevel | OT_INTEGER | 0 | Enable XML | >| | | | logfiles and | >| | | | writing | >| | | | interval | >+-----------------+-----------------+-----------------+-----------------+ >| LogResult | OT_INTEGER | 0 | Enable XML | >| | | | result logging | >| | | | and detail | >| | | | level | >+-----------------+-----------------+-----------------+-----------------+ >| LowPassAlphaF | OT_REAL | 0.950 | Lowpass-filter | >| | | | update factor | >| | | | for objective | >| | | | values | >+-----------------+-----------------+-----------------+-----------------+ >| LowPassAlphaG | OT_REAL | 0.950 | Lowpass-filter | >| | | | update factor | >| | | | for constraint | >| | | | values | >+-----------------+-----------------+-----------------+-----------------+ >| LowPassAlphaMer | OT_REAL | 0.100 | Lowpass-filter | >| it | | | update factor | >| | | | for merit | >| | | | function values | >+-----------------+-----------------+-----------------+-----------------+ >| LowPassFilter | OT_BOOLEAN | True | Enable lowpass- | >| | | | filter | >| | | | termination | >| | | | criterion | >+-----------------+-----------------+-----------------+-----------------+ >| MAPivotThreshol | OT_REAL | 0.000 | Pivoting | >| d | | | tolerance for | >| | | | MA solvers | >+-----------------+-----------------+-----------------+-----------------+ >| MatrixCC | OT_BOOLEAN | False | Not to be | >| | | | included into a | >| | | | parameter file! | >+-----------------+-----------------+-----------------+-----------------+ >| MaxCalls | OT_INTEGER | 2.147e+09 | Upper bound to | >| | | | Reverse | >| | | | Communication | >| | | | calls | >+-----------------+-----------------+-----------------+-----------------+ >| MaxForce | OT_INTEGER | 1000 | Maximum number | >| | | | of Force | >| | | | recovery | >| | | | strategy steps | >+-----------------+-----------------+-----------------+-----------------+ >| MaxGPart | OT_INTEGER | 1 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| MaxIter | OT_INTEGER | 500 | Upper bound on | >| | | | major | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| MaxLScounter | OT_INTEGER | 3 | Control | >| | | | activation of | >| | | | Filter | >| | | | acceleration | >| | | | heuristics | >+-----------------+-----------------+-----------------+-----------------+ >| MaxNorm | OT_BOOLEAN | True | Select max-norm | >| | | | instead of | >| | | | 1-norm in | >| | | | Filter | >+-----------------+-----------------+-----------------+-----------------+ >| MeritFunction | OT_INTEGER | 4 | Select merit | >| | | | function and | >| | | | penalty update | >| | | | [0, 3..5] | >+-----------------+-----------------+-----------------+-----------------+ >| MeritGradTol | OT_REAL | 0.000 | Threshold of | >| | | | meritfunction | >| | | | gradient for | >| | | | increasing | >| | | | Hessian | >| | | | regularisation | >+-----------------+-----------------+-----------------+-----------------+ >| MinBettsTau | OT_REAL | 0.000 | Lower bound for | >| | | | Betts' update | >| | | | dampening term | >+-----------------+-----------------+-----------------+-----------------+ >| MoreRelax | OT_BOOLEAN | False | Introduce one | >| | | | relaxation | >| | | | variable for | >| | | | every | >| | | | constraint | >+-----------------+-----------------+-----------------+-----------------+ >| NLPmethod | OT_INTEGER | 1 | Select (1) | >| | | | Meritfunction | >| | | | or (3) Filter | >| | | | globalisation | >+-----------------+-----------------+-----------------+-----------------+ >| NLPprint | OT_INTEGER | 2 | NLP print level | >| | | | [-1..4] | >+-----------------+-----------------+-----------------+-----------------+ >| PairMethod | OT_INTEGER | 1 | Select method | >| | | | to determine | >| | | | graph colouring | >| | | | pairgroups | >+-----------------+-----------------+-----------------+-----------------+ >| PenUpdEpsBar | OT_REAL | 0.900 | Penalty update | >| | | | parameter | >| | | | factor for | >| | | | MeritFunction = | >| | | | 3 | >+-----------------+-----------------+-----------------+-----------------+ >| PenUpdEpsKFac | OT_REAL | 2 | Penalty update | >| | | | parameter | >| | | | factor for | >| | | | MeritFunction = | >| | | | 4 | >+-----------------+-----------------+-----------------+-----------------+ >| PenUpdEpsKSeque | OT_INTEGER | 2 | Penalty update | >| nce | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| PenUpdMaxDeltaK | OT_REAL | 11 | Max penalty for | >| | | | MeritFunction = | >| | | | 4 | >+-----------------+-----------------+-----------------+-----------------+ >| PenUpdMaxFac | OT_REAL | 100000000 | Max factor for | >| | | | increasing | >| | | | penalty for | >| | | | MeritFunction = | >| | | | 4 | >+-----------------+-----------------+-----------------+-----------------+ >| PenUpdRBar | OT_REAL | 2 | Penalty update | >| | | | parameter for | >| | | | MeritFunction = | >| | | | 3 | >+-----------------+-----------------+-----------------+-----------------+ >| PrecisionF | OT_REAL | 0.000 | (currently | >| | | | unused) | >| | | | Relative | >| | | | precision of | >| | | | objective | >+-----------------+-----------------+-----------------+-----------------+ >| PrecisionG | OT_REAL | 0.000 | (currently | >| | | | unused) | >| | | | Relative | >| | | | precision of | >| | | | constraints | >+-----------------+-----------------+-----------------+-----------------+ >| QPscaleParam | OT_REAL | 0 | (currently | >| | | | unused) Scaling | >| | | | factor for QP | >+-----------------+-----------------+-----------------+-----------------+ >| QuadraticProble | OT_BOOLEAN | False | Not to be | >| m | | | included into a | >| | | | parameter file! | >+-----------------+-----------------+-----------------+-----------------+ >| ReduceBettsTau | OT_REAL | 0.300 | Decrease factor | >| | | | for Betts' | >| | | | update | >| | | | dampening term | >+-----------------+-----------------+-----------------+-----------------+ >| RegStrategy | OT_INTEGER | 1 | Select Hessian | >| | | | regularisation | >| | | | strategy in | >| | | | Filter | >+-----------------+-----------------+-----------------+-----------------+ >| ReinitFilter | OT_BOOLEAN | False | Enables Filter- | >| | | | reinitialisatio | >| | | | n accelerating | >| | | | heuristic | >+-----------------+-----------------+-----------------+-----------------+ >| RelaxMaxDelta | OT_REAL | 0.920 | Upper bound for | >| | | | accepting the | >| | | | constraint | >| | | | relaxation | >| | | | variable | >+-----------------+-----------------+-----------------+-----------------+ >| RelaxMaxPen | OT_REAL | 50000000 | Upper bound on | >| | | | the constraint | >| | | | relaxation | >| | | | penalty | >+-----------------+-----------------+-----------------+-----------------+ >| RelaxRho | OT_REAL | 6 | Update factor | >| | | | for the | >| | | | constraint | >| | | | relaxation | >| | | | penalty | >+-----------------+-----------------+-----------------+-----------------+ >| RelaxStart | OT_REAL | 1 | Initial value | >| | | | of the | >| | | | constraint | >| | | | relaxation | >| | | | penalty | >+-----------------+-----------------+-----------------+-----------------+ >| RestUntilFeas | OT_BOOLEAN | False | Do restoration | >| | | | until a | >| | | | feasible | >| | | | solution is | >| | | | found | >+-----------------+-----------------+-----------------+-----------------+ >| ScaleConIter | OT_BOOLEAN | False | Scale | >| | | | constraints in | >| | | | every iteration | >+-----------------+-----------------+-----------------+-----------------+ >| ScaleFacObj | OT_REAL | 10 | Value to scale | >| | | | large objective | >| | | | functions to | >+-----------------+-----------------+-----------------+-----------------+ >| ScaleFacQP | OT_REAL | 10 | Upper bound on | >| | | | resulting | >| | | | matrix norm for | >| | | | QP scaling | >+-----------------+-----------------+-----------------+-----------------+ >| ScaledFD | OT_BOOLEAN | True | Use a scaled | >| | | | perturbation | >| | | | for finite | >| | | | differences | >+-----------------+-----------------+-----------------+-----------------+ >| ScaledKKT | OT_BOOLEAN | True | Scale KKT | >| | | | conditions | >+-----------------+-----------------+-----------------+-----------------+ >| ScaledObj | OT_BOOLEAN | True | Scale the | >| | | | objective | >| | | | function | >+-----------------+-----------------+-----------------+-----------------+ >| ScaledQP | OT_BOOLEAN | True | Scale some | >| | | | matrices handed | >| | | | to the QP | >+-----------------+-----------------+-----------------+-----------------+ >| StartBettsTau | OT_REAL | 0.100 | Initial value | >| | | | for Betts' | >| | | | update | >| | | | dampening term | >+-----------------+-----------------+-----------------+-----------------+ >| SwitchingDelta | OT_REAL | 0.010 | Filter | >| | | | switching | >| | | | condition | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| SwitchingSCV | OT_REAL | 1.100 | Filter | >| | | | switching | >| | | | condition | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| SwitchingSF | OT_REAL | 2.300 | Filter | >| | | | switching | >| | | | condition | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| TakeQPSol | OT_BOOLEAN | False | Evaluate QP | >| | | | search | >| | | | direction | >| | | | regardless of | >| | | | convergence | >+-----------------+-----------------+-----------------+-----------------+ >| Timeout | OT_REAL | 300 | Timeout in | >| | | | seconds | >+-----------------+-----------------+-----------------+-----------------+ >| TolComp | OT_REAL | 0.001 | Complementarity | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| TolFeas | OT_REAL | 0.000 | Feasibility | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| TolOpti | OT_REAL | 0.000 | Optimality | >| | | | tolerance | >+-----------------+-----------------+-----------------+-----------------+ >| TolWeakActive | OT_REAL | 1 | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| TooBig | OT_BOOLEAN | True | Enable too-big | >| | | | termination | >| | | | heuristics | >+-----------------+-----------------+-----------------+-----------------+ >| TooBigCV | OT_REAL | 1.000e+25 | Upper bound on | >| | | | constraint | >| | | | violation for | >| | | | too-big | >| | | | heuristic | >+-----------------+-----------------+-----------------+-----------------+ >| TooBigKKT | OT_REAL | 1.000e+30 | Upper bound on | >| | | | KKT values for | >| | | | too-big | >| | | | heuristic | >+-----------------+-----------------+-----------------+-----------------+ >| UserDF | OT_BOOLEAN | True | Objective | >| | | | gradient values | >| | | | supplied by | >| | | | caller | >+-----------------+-----------------+-----------------+-----------------+ >| UserDG | OT_BOOLEAN | True | Jacobian values | >| | | | supplied by | >| | | | caller | >+-----------------+-----------------+-----------------+-----------------+ >| UserHM | OT_BOOLEAN | True | Hessian values | >| | | | supplied by | >| | | | caller | >+-----------------+-----------------+-----------------+-----------------+ >| UserHMstructure | OT_INTEGER | 2 | Enable | >| | | | automatic | >| | | | Hessian | >| | | | structure | >| | | | generation or | >| | | | checking | >+-----------------+-----------------+-----------------+-----------------+ >| WeakActiveSet | OT_BOOLEAN | False | (experimental) | >+-----------------+-----------------+-----------------+-----------------+ >| eps | OT_REAL | 0.000 | Machine epsilon | >+-----------------+-----------------+-----------------+-----------------+ >| internalParChan | OT_INTEGER | 0 | Counter for | >| ged | | | changed | >| | | | parameters. | >| | | | Internal use | >| | | | only. | >+-----------------+-----------------+-----------------+-----------------+ >| print_time | OT_BOOLEAN | True | Print | >| | | | information | >| | | | about execution | >| | | | time | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipBarrier | OT_REAL | 7.800 | IP barrier | >| | | | parameter. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipComTol | OT_REAL | 0.000 | IP | >| | | | complementarity | >| | | | tolerance. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipFracBound | OT_REAL | 0.880 | IP fraction-to- | >| | | | the-boundary | >| | | | parameter. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipLsMethod | OT_STRING | None | Select the | >| | | | direct linear | >| | | | solver used by | >| | | | the IP method. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipMinAlpha | OT_REAL | 0.000 | IP line search | >| | | | minimum step | >| | | | size. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipRelaxDiv | OT_REAL | 2 | The relaxation | >| | | | term is divided | >| | | | by this value | >| | | | if successful. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipRelaxMax | OT_REAL | 0.000 | Maximum | >| | | | relaxation | >| | | | value. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipRelaxMin | OT_REAL | 0.000 | Mimimum | >| | | | relaxation | >| | | | value. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipRelaxMult | OT_REAL | 10 | The relaxation | >| | | | term is | >| | | | multiplied by | >| | | | this value if | >| | | | unsuccessful. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipResTol | OT_REAL | 0.000 | IP residuals | >| | | | tolerance. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_ipTryRelax | OT_BOOLEAN | True | Enable | >| | | | relaxation | >| | | | strategy when | >| | | | encountering an | >| | | | error. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_lsItMaxIter | OT_INTEGER | 1000 | Maximum number | >| | | | of iterations | >| | | | of the | >| | | | iterative | >| | | | linear solvers. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_lsItMethod | OT_STRING | None | Select the | >| | | | iterative | >| | | | linear solver. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_lsItPrecondM | OT_STRING | None | Select | >| ethod | | | preconditioner | >| | | | for the | >| | | | iterative | >| | | | linear solver. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_lsRefineMaxI | OT_INTEGER | 10 | Maximum number | >| ter | | | of iterative | >| | | | refinement | >| | | | steps of the | >| | | | direct linear | >| | | | solvers. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_lsScale | OT_BOOLEAN | True | Enables scaling | >| | | | on linear | >| | | | solver level. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_lsTol | OT_REAL | 0.000 | Tolerance for | >| | | | the linear | >| | | | solver. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_lsTrySimple | OT_BOOLEAN | False | Some matrices | >| | | | can be solved | >| | | | without calling | >| | | | a linear | >| | | | equation solver | >| | | | .Currently only | >| | | | diagonal | >| | | | matrices are | >| | | | supported.Non- | >| | | | diagonal | >| | | | matrices will | >| | | | besolved with | >| | | | the chosen | >| | | | linear equation | >| | | | solver. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_maxIter | OT_INTEGER | 80 | Imposes an | >| | | | upper limit on | >| | | | the number of | >| | | | minor solver | >| | | | iterations, | >| | | | i.e. for the | >| | | | quadratic | >| | | | subproblem | >| | | | solver.If the | >| | | | limit is | >| | | | reached before | >| | | | convergence, | >| | | | WORHP will | >| | | | activate QP | >| | | | recovery | >| | | | strategies to | >| | | | prevent a | >| | | | solver | >| | | | breakdown. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_method | OT_STRING | None | Select the | >| | | | solution method | >| | | | used by the QP | >| | | | solver. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_nsnBeta | OT_REAL | 0.900 | NSN stepsize | >| | | | decrease | >| | | | factor. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_nsnGradStep | OT_BOOLEAN | True | Enable gradient | >| | | | steps in the | >| | | | NSN method. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_nsnKKT | OT_REAL | 0.000 | NSN KKT | >| | | | tolerance. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_nsnLsMethod | OT_STRING | None | Select the | >| | | | direct linear | >| | | | solver used by | >| | | | the NSN method. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_nsnMinAlpha | OT_REAL | 0.000 | NSN line search | >| | | | minimum step | >| | | | size. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_nsnSigma | OT_REAL | 0.010 | NSN line search | >| | | | slope | >| | | | parameter. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_printLevel | OT_STRING | None | Controls the | >| | | | amount of QP | >| | | | solver output. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_scaleIntern | OT_BOOLEAN | False | Enable scaling | >| | | | on QP level. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_strict | OT_BOOLEAN | True | Use strict | >| | | | termination | >| | | | criteria in IP | >| | | | method. | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-------------+ >| Id | >+=============+ >| eval_f | >+-------------+ >| eval_g | >+-------------+ >| eval_grad_f | >+-------------+ >| eval_h | >+-------------+ >| eval_jac_g | >+-------------+ > >>List of available stats > >+--------------------+ >| Id | >+====================+ >| iter_count | >+--------------------+ >| iteration | >+--------------------+ >| iterations | >+--------------------+ >| n_eval_f | >+--------------------+ >| n_eval_g | >+--------------------+ >| n_eval_grad_f | >+--------------------+ >| n_eval_h | >+--------------------+ >| n_eval_jac_g | >+--------------------+ >| return_code | >+--------------------+ >| return_status | >+--------------------+ >| t_callback_fun | >+--------------------+ >| t_callback_prepare | >+--------------------+ >| t_eval_f | >+--------------------+ >| t_eval_g | >+--------------------+ >| t_eval_grad_f | >+--------------------+ >| t_eval_h | >+--------------------+ >| t_eval_jac_g | >+--------------------+ >| t_mainloop | >+--------------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >scpgen >------ > > > >A structure-exploiting sequential quadratic programming (to be come >sequential convex programming) method for nonlinear programming. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| beta | OT_REAL | 0.800 | Line-search | >| | | | parameter, | >| | | | restoration | >| | | | factor of | >| | | | stepsize | >+-----------------+-----------------+-----------------+-----------------+ >| c1 | OT_REAL | 0.000 | Armijo | >| | | | condition, | >| | | | coefficient of | >| | | | decrease in | >| | | | merit | >+-----------------+-----------------+-----------------+-----------------+ >| codegen | OT_BOOLEAN | false | C-code | >| | | | generation | >+-----------------+-----------------+-----------------+-----------------+ >| compiler | OT_STRING | "gcc -fPIC -O2" | Compiler | >| | | | command to be | >| | | | used for | >| | | | compiling | >| | | | generated code | >+-----------------+-----------------+-----------------+-----------------+ >| hessian_approxi | OT_STRING | "exact" | gauss- | >| mation | | | newton|exact | >+-----------------+-----------------+-----------------+-----------------+ >| lbfgs_memory | OT_INTEGER | 10 | Size of L-BFGS | >| | | | memory. | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter | OT_INTEGER | 50 | Maximum number | >| | | | of SQP | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter_ls | OT_INTEGER | 1 | Maximum number | >| | | | of linesearch | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| merit_memsize | OT_INTEGER | 4 | Size of memory | >| | | | to store | >| | | | history of | >| | | | merit function | >| | | | values | >+-----------------+-----------------+-----------------+-----------------+ >| merit_start | OT_REAL | 0.000 | Lower bound for | >| | | | the merit | >| | | | function | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| name_x | OT_STRINGVECTOR | GenericType() | Names of the | >| | | | variables. | >+-----------------+-----------------+-----------------+-----------------+ >| print_header | OT_BOOLEAN | true | Print the | >| | | | header with | >| | | | problem | >| | | | statistics | >+-----------------+-----------------+-----------------+-----------------+ >| print_time | OT_BOOLEAN | true | Print | >| | | | information | >| | | | about execution | >| | | | time | >+-----------------+-----------------+-----------------+-----------------+ >| print_x | OT_INTEGERVECTO | GenericType() | Which variables | >| | R | | to print. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_solver | OT_STRING | GenericType() | The QP solver | >| | | | to be used by | >| | | | the SQP method | >+-----------------+-----------------+-----------------+-----------------+ >| qp_solver_optio | OT_DICTIONARY | GenericType() | Options to be | >| ns | | | passed to the | >| | | | QP solver | >+-----------------+-----------------+-----------------+-----------------+ >| reg_threshold | OT_REAL | 0.000 | Threshold for | >| | | | the | >| | | | regularization. | >+-----------------+-----------------+-----------------+-----------------+ >| regularize | OT_BOOLEAN | false | Automatic | >| | | | regularization | >| | | | of Lagrange | >| | | | Hessian. | >+-----------------+-----------------+-----------------+-----------------+ >| tol_du | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | dual | >| | | | infeasability | >+-----------------+-----------------+-----------------+-----------------+ >| tol_pr | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | primal | >| | | | infeasibility | >+-----------------+-----------------+-----------------+-----------------+ >| tol_pr_step | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | the step size | >+-----------------+-----------------+-----------------+-----------------+ >| tol_reg | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | regularization | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-------------+ >| Id | >+=============+ >| dx | >+-------------+ >| eval_f | >+-------------+ >| eval_g | >+-------------+ >| eval_grad_f | >+-------------+ >| eval_h | >+-------------+ >| eval_jac_g | >+-------------+ >| qp | >+-------------+ > >>List of available stats > >+------------+ >| Id | >+============+ >| iter_count | >+------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >sqpmethod >--------- > > > >A textbook SQPMethod > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| beta | OT_REAL | 0.800 | Line-search | >| | | | parameter, | >| | | | restoration | >| | | | factor of | >| | | | stepsize | >+-----------------+-----------------+-----------------+-----------------+ >| c1 | OT_REAL | 0.000 | Armijo | >| | | | condition, | >| | | | coefficient of | >| | | | decrease in | >| | | | merit | >+-----------------+-----------------+-----------------+-----------------+ >| hessian_approxi | OT_STRING | "exact" | limited- | >| mation | | | memory|exact | >+-----------------+-----------------+-----------------+-----------------+ >| lbfgs_memory | OT_INTEGER | 10 | Size of L-BFGS | >| | | | memory. | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter | OT_INTEGER | 50 | Maximum number | >| | | | of SQP | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter_ls | OT_INTEGER | 3 | Maximum number | >| | | | of linesearch | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| merit_memory | OT_INTEGER | 4 | Size of memory | >| | | | to store | >| | | | history of | >| | | | merit function | >| | | | values | >+-----------------+-----------------+-----------------+-----------------+ >| min_step_size | OT_REAL | 0.000 | The size (inf- | >| | | | norm) of the | >| | | | step size | >| | | | should not | >| | | | become smaller | >| | | | than this. | >+-----------------+-----------------+-----------------+-----------------+ >| print_header | OT_BOOLEAN | true | Print the | >| | | | header with | >| | | | problem | >| | | | statistics | >+-----------------+-----------------+-----------------+-----------------+ >| print_time | OT_BOOLEAN | true | Print | >| | | | information | >| | | | about execution | >| | | | time | >+-----------------+-----------------+-----------------+-----------------+ >| qp_solver | OT_STRING | GenericType() | The QP solver | >| | | | to be used by | >| | | | the SQP method | >+-----------------+-----------------+-----------------+-----------------+ >| qp_solver_optio | OT_DICTIONARY | GenericType() | Options to be | >| ns | | | passed to the | >| | | | QP solver | >+-----------------+-----------------+-----------------+-----------------+ >| regularize | OT_BOOLEAN | false | Automatic | >| | | | regularization | >| | | | of Lagrange | >| | | | Hessian. | >+-----------------+-----------------+-----------------+-----------------+ >| tol_du | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | dual | >| | | | infeasability | >+-----------------+-----------------+-----------------+-----------------+ >| tol_pr | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | primal | >| | | | infeasibility | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-------------+ >| Id | >+=============+ >| bfgs | >+-------------+ >| dx | >+-------------+ >| eval_f | >+-------------+ >| eval_g | >+-------------+ >| eval_grad_f | >+-------------+ >| eval_h | >+-------------+ >| eval_jac_g | >+-------------+ >| qp | >+-------------+ > >>List of available stats > >+--------------------+ >| Id | >+====================+ >| iter_count | >+--------------------+ >| iteration | >+--------------------+ >| iterations | >+--------------------+ >| n_eval_f | >+--------------------+ >| n_eval_g | >+--------------------+ >| n_eval_grad_f | >+--------------------+ >| n_eval_h | >+--------------------+ >| n_eval_jac_g | >+--------------------+ >| return_status | >+--------------------+ >| t_callback_fun | >+--------------------+ >| t_callback_prepare | >+--------------------+ >| t_eval_f | >+--------------------+ >| t_eval_g | >+--------------------+ >| t_eval_grad_f | >+--------------------+ >| t_eval_h | >+--------------------+ >| t_eval_jac_g | >+--------------------+ >| t_mainloop | >+--------------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >stabilizedsqp >------------- > > > >Stabilized Sequential Quadratic Programming method. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| TReta1 | OT_REAL | 0.800 | Required | >| | | | predicted / | >| | | | actual decrease | >| | | | for TR increase | >+-----------------+-----------------+-----------------+-----------------+ >| TReta2 | OT_REAL | 0.200 | Required | >| | | | predicted / | >| | | | actual decrease | >| | | | for TR decrease | >+-----------------+-----------------+-----------------+-----------------+ >| alphaMin | OT_REAL | 0.001 | Used to check | >| | | | whether to | >| | | | increase rho. | >+-----------------+-----------------+-----------------+-----------------+ >| beta | OT_REAL | 0.500 | Line-search | >| | | | parameter, | >| | | | restoration | >| | | | factor of | >| | | | stepsize | >+-----------------+-----------------+-----------------+-----------------+ >| c1 | OT_REAL | 0.001 | Armijo | >| | | | condition, | >| | | | coefficient of | >| | | | decrease in | >| | | | merit | >+-----------------+-----------------+-----------------+-----------------+ >| dvMax0 | OT_REAL | 100 | Parameter used | >| | | | to defined the | >| | | | max step | >| | | | length. | >+-----------------+-----------------+-----------------+-----------------+ >| eps_active | OT_REAL | 0.000 | Threshold for | >| | | | the epsilon- | >| | | | active set. | >+-----------------+-----------------+-----------------+-----------------+ >| gamma1 | OT_REAL | 2 | Trust region | >| | | | increase | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| gamma2 | OT_REAL | 1 | Trust region | >| | | | update | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| gamma3 | OT_REAL | 1 | Trust region | >| | | | decrease | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| hessian_approxi | OT_STRING | "exact" | limited- | >| mation | | | memory|exact | >+-----------------+-----------------+-----------------+-----------------+ >| lbfgs_memory | OT_INTEGER | 10 | Size of L-BFGS | >| | | | memory. | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter | OT_INTEGER | 100 | Maximum number | >| | | | of SQP | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| max_iter_ls | OT_INTEGER | 20 | Maximum number | >| | | | of linesearch | >| | | | iterations | >+-----------------+-----------------+-----------------+-----------------+ >| max_time | OT_REAL | 1.000e+12 | Timeout | >+-----------------+-----------------+-----------------+-----------------+ >| merit_memory | OT_INTEGER | 4 | Size of memory | >| | | | to store | >| | | | history of | >| | | | merit function | >| | | | values | >+-----------------+-----------------+-----------------+-----------------+ >| min_step_size | OT_REAL | 0.000 | The size (inf- | >| | | | norm) of the | >| | | | step size | >| | | | should not | >| | | | become smaller | >| | | | than this. | >+-----------------+-----------------+-----------------+-----------------+ >| muR0 | OT_REAL | 0.000 | Initial choice | >| | | | of | >| | | | regularization | >| | | | parameter | >+-----------------+-----------------+-----------------+-----------------+ >| nu | OT_REAL | 1 | Parameter for | >| | | | primal-dual | >| | | | augmented | >| | | | Lagrangian. | >+-----------------+-----------------+-----------------+-----------------+ >| phiWeight | OT_REAL | 0.000 | Weight used in | >| | | | pseudo-filter. | >+-----------------+-----------------+-----------------+-----------------+ >| print_header | OT_BOOLEAN | true | Print the | >| | | | header with | >| | | | problem | >| | | | statistics | >+-----------------+-----------------+-----------------+-----------------+ >| regularize | OT_BOOLEAN | false | Automatic | >| | | | regularization | >| | | | of Lagrange | >| | | | Hessian. | >+-----------------+-----------------+-----------------+-----------------+ >| stabilized_qp_s | OT_STRING | GenericType() | The Stabilized | >| olver | | | QP solver to be | >| | | | used by the SQP | >| | | | method | >+-----------------+-----------------+-----------------+-----------------+ >| stabilized_qp_s | OT_DICTIONARY | GenericType() | Options to be | >| olver_options | | | passed to the | >| | | | Stabilized QP | >| | | | solver | >+-----------------+-----------------+-----------------+-----------------+ >| tau0 | OT_REAL | 0.010 | Initial | >| | | | parameter for | >| | | | the merit | >| | | | function | >| | | | optimality | >| | | | threshold. | >+-----------------+-----------------+-----------------+-----------------+ >| tol_du | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | dual | >| | | | infeasability | >+-----------------+-----------------+-----------------+-----------------+ >| tol_pr | OT_REAL | 0.000 | Stopping | >| | | | criterion for | >| | | | primal | >| | | | infeasibility | >+-----------------+-----------------+-----------------+-----------------+ >| yEinitial | OT_STRING | "simple" | Initial | >| | | | multiplier. | >| | | | Simple (all | >| | | | zero) or least | >| | | | (LSQ). | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available monitors > >+-------------+ >| Id | >+=============+ >| dx | >+-------------+ >| eval_f | >+-------------+ >| eval_g | >+-------------+ >| eval_grad_f | >+-------------+ >| eval_h | >+-------------+ >| eval_jac_g | >+-------------+ >| qp | >+-------------+ > >>List of available stats > >+---------------+ >| Id | >+===============+ >| iter_count | >+---------------+ >| return_status | >+---------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: nlp_solver.hpp -} newtype NlpSolver = NlpSolver (ForeignPtr NlpSolver') -- typeclass decl class NlpSolverClass a where castNlpSolver :: a -> NlpSolver instance NlpSolverClass NlpSolver where castNlpSolver = id -- baseclass instances instance FunctionClass NlpSolver where castFunction (NlpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass NlpSolver where castOptionsFunctionality (NlpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass NlpSolver where castPrintableObject (NlpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass NlpSolver where castSharedObject (NlpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass NlpSolver where castIOInterfaceFunction (NlpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal NlpSolver (Ptr NlpSolver') where marshal (NlpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (NlpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__NlpSolver" c_delete_casadi__NlpSolver :: FunPtr (Ptr NlpSolver' -> IO ()) instance WrapReturn (Ptr NlpSolver') NlpSolver where wrapReturn = (fmap NlpSolver) . (newForeignPtr c_delete_casadi__NlpSolver) -- raw decl data Nullspace' -- data decl {-| >Base class for nullspace construction. > >Constructs a basis for the null-space of a fat matrix A. i.e. finds Z such >that AZ = 0 holds. > >The nullspace is also known as the orthogonal complement of the rowspace of >a matrix. > >It is assumed that the matrix A is of full rank. > >Implementations are not required to construct an orthogonal or orthonormal >basis Joris Gillis > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| dense | OT_BOOLEAN | true | Indicates | casadi::Null | >| | | | that dense | spaceInterna | >| | | | matrices can | l | >| | | | be assumed | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: nullspace.hpp -} newtype Nullspace = Nullspace (ForeignPtr Nullspace') -- typeclass decl class NullspaceClass a where castNullspace :: a -> Nullspace instance NullspaceClass Nullspace where castNullspace = id -- baseclass instances instance FunctionClass Nullspace where castFunction (Nullspace x) = Function (castForeignPtr x) instance OptionsFunctionalityClass Nullspace where castOptionsFunctionality (Nullspace x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass Nullspace where castPrintableObject (Nullspace x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Nullspace where castSharedObject (Nullspace x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass Nullspace where castIOInterfaceFunction (Nullspace x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal Nullspace (Ptr Nullspace') where marshal (Nullspace x) = return (unsafeForeignPtrToPtr x) marshalFree (Nullspace x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Nullspace" c_delete_casadi__Nullspace :: FunPtr (Ptr Nullspace' -> IO ()) instance WrapReturn (Ptr Nullspace') Nullspace where wrapReturn = (fmap Nullspace) . (newForeignPtr c_delete_casadi__Nullspace) -- raw decl data OCPSolver' -- data decl {-| >Base class for OCP solvers. > >Joel Andersson > >>Input scheme: casadi::OCPInput (OCP_NUM_IN = 13) [ocpIn] > >+------------+--------+----------------------------------------------+ >| Full name | Short | Description | >+============+========+==============================================+ >| OCP_LBX | lbx | States lower bounds (nx x (ns+1)) . | >+------------+--------+----------------------------------------------+ >| OCP_UBX | ubx | States upper bounds (nx x (ns+1)) . | >+------------+--------+----------------------------------------------+ >| OCP_X_INIT | x_init | States initial guess (nx x (ns+1)) . | >+------------+--------+----------------------------------------------+ >| OCP_LBU | lbu | Controls lower bounds (nu x ns) . | >+------------+--------+----------------------------------------------+ >| OCP_UBU | ubu | Controls upper bounds (nu x ns) . | >+------------+--------+----------------------------------------------+ >| OCP_U_INIT | u_init | Controls initial guess (nu x ns) . | >+------------+--------+----------------------------------------------+ >| OCP_LBP | lbp | Parameters lower bounds (np x 1) . | >+------------+--------+----------------------------------------------+ >| OCP_UBP | ubp | Parameters upper bounds (np x 1) . | >+------------+--------+----------------------------------------------+ >| OCP_P_INIT | p_init | Parameters initial guess (np x 1) . | >+------------+--------+----------------------------------------------+ >| OCP_LBH | lbh | Point constraint lower bound (nh x (ns+1)) . | >+------------+--------+----------------------------------------------+ >| OCP_UBH | ubh | Point constraint upper bound (nh x (ns+1)) . | >+------------+--------+----------------------------------------------+ >| OCP_LBG | lbg | Lower bound for the coupling constraints . | >+------------+--------+----------------------------------------------+ >| OCP_UBG | ubg | Upper bound for the coupling constraints . | >+------------+--------+----------------------------------------------+ > >>Output scheme: casadi::OCPOutput (OCP_NUM_OUT = 4) [ocpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| OCP_X_OPT | x_opt | Optimal state | >| | | trajectory . | >+------------------------+------------------------+------------------------+ >| OCP_U_OPT | u_opt | Optimal control | >| | | trajectory . | >+------------------------+------------------------+------------------------+ >| OCP_P_OPT | p_opt | Optimal parameters . | >+------------------------+------------------------+------------------------+ >| OCP_COST | cost | Objective/cost | >| | | function for optimal | >| | | solution (1 x 1) . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| final_time | OT_REAL | 1 | | casadi::OCPS | >| | | | | olverInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| number_of_gr | OT_INTEGER | 20 | | casadi::OCPS | >| id_points | | | | olverInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| number_of_pa | OT_INTEGER | 0 | | casadi::OCPS | >| rameters | | | | olverInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: ocp_solver.hpp -} newtype OCPSolver = OCPSolver (ForeignPtr OCPSolver') -- typeclass decl class OCPSolverClass a where castOCPSolver :: a -> OCPSolver instance OCPSolverClass OCPSolver where castOCPSolver = id -- baseclass instances instance FunctionClass OCPSolver where castFunction (OCPSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass OCPSolver where castOptionsFunctionality (OCPSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass OCPSolver where castPrintableObject (OCPSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass OCPSolver where castSharedObject (OCPSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass OCPSolver where castIOInterfaceFunction (OCPSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal OCPSolver (Ptr OCPSolver') where marshal (OCPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (OCPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__OCPSolver" c_delete_casadi__OCPSolver :: FunPtr (Ptr OCPSolver' -> IO ()) instance WrapReturn (Ptr OCPSolver') OCPSolver where wrapReturn = (fmap OCPSolver) . (newForeignPtr c_delete_casadi__OCPSolver) -- raw decl data OptionsFunctionality' -- data decl {-| >Provides options setting/getting functionality. > >Gives a derived class the ability to set and retrieve options in a >convenient way. It also contains error checking, making sure that the option >exists and that the value type is correct. > >A derived class should add option names, types and default values to the >corresponding vectors. > >Joel Andersson > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: options_functionality.hpp -} newtype OptionsFunctionality = OptionsFunctionality (ForeignPtr OptionsFunctionality') -- typeclass decl class OptionsFunctionalityClass a where castOptionsFunctionality :: a -> OptionsFunctionality instance OptionsFunctionalityClass OptionsFunctionality where castOptionsFunctionality = id -- baseclass instances instance PrintableObjectClass OptionsFunctionality where castPrintableObject (OptionsFunctionality x) = PrintableObject (castForeignPtr x) instance SharedObjectClass OptionsFunctionality where castSharedObject (OptionsFunctionality x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal OptionsFunctionality (Ptr OptionsFunctionality') where marshal (OptionsFunctionality x) = return (unsafeForeignPtrToPtr x) marshalFree (OptionsFunctionality x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__OptionsFunctionality" c_delete_casadi__OptionsFunctionality :: FunPtr (Ptr OptionsFunctionality' -> IO ()) instance WrapReturn (Ptr OptionsFunctionality') OptionsFunctionality where wrapReturn = (fmap OptionsFunctionality) . (newForeignPtr c_delete_casadi__OptionsFunctionality) -- raw decl data Parallelizer' -- data decl {-| >Parallelizer execution of functions. > >Joel Andersson > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| parallelizat | OT_STRING | "serial" | (serial|open | casadi::Para | >| ion | | | mp|mpi) | llelizerInte | >| | | | | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available stats > >+-----------------+------------------------------+ >| Id | Used in | >+=================+==============================+ >| max_threads | casadi::ParallelizerInternal | >+-----------------+------------------------------+ >| num_threads | casadi::ParallelizerInternal | >+-----------------+------------------------------+ >| task_allocation | casadi::ParallelizerInternal | >+-----------------+------------------------------+ >| task_cputime | casadi::ParallelizerInternal | >+-----------------+------------------------------+ >| task_endtime | casadi::ParallelizerInternal | >+-----------------+------------------------------+ >| task_order | casadi::ParallelizerInternal | >+-----------------+------------------------------+ >| task_starttime | casadi::ParallelizerInternal | >+-----------------+------------------------------+ > >Diagrams >-------- > > > >C++ includes: parallelizer.hpp -} newtype Parallelizer = Parallelizer (ForeignPtr Parallelizer') -- typeclass decl class ParallelizerClass a where castParallelizer :: a -> Parallelizer instance ParallelizerClass Parallelizer where castParallelizer = id -- baseclass instances instance FunctionClass Parallelizer where castFunction (Parallelizer x) = Function (castForeignPtr x) instance OptionsFunctionalityClass Parallelizer where castOptionsFunctionality (Parallelizer x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass Parallelizer where castPrintableObject (Parallelizer x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Parallelizer where castSharedObject (Parallelizer x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass Parallelizer where castIOInterfaceFunction (Parallelizer x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal Parallelizer (Ptr Parallelizer') where marshal (Parallelizer x) = return (unsafeForeignPtrToPtr x) marshalFree (Parallelizer x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Parallelizer" c_delete_casadi__Parallelizer :: FunPtr (Ptr Parallelizer' -> IO ()) instance WrapReturn (Ptr Parallelizer') Parallelizer where wrapReturn = (fmap Parallelizer) . (newForeignPtr c_delete_casadi__Parallelizer) -- raw decl data PrintableObject' -- data decl {-| >Base class for objects that have a natural string representation. > >Joel Andersson > >C++ includes: printable_object.hpp -} newtype PrintableObject = PrintableObject (ForeignPtr PrintableObject') -- typeclass decl class PrintableObjectClass a where castPrintableObject :: a -> PrintableObject instance PrintableObjectClass PrintableObject where castPrintableObject = id -- baseclass instances -- helper instances instance Marshal PrintableObject (Ptr PrintableObject') where marshal (PrintableObject x) = return (unsafeForeignPtrToPtr x) marshalFree (PrintableObject x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__PrintableObject" c_delete_casadi__PrintableObject :: FunPtr (Ptr PrintableObject' -> IO ()) instance WrapReturn (Ptr PrintableObject') PrintableObject where wrapReturn = (fmap PrintableObject) . (newForeignPtr c_delete_casadi__PrintableObject) -- raw decl data QcqpSolver' -- data decl {-| >QcqpSolver. > >Solves the following strictly convex problem: > > > >:: > > min 1/2 x' H x + g' x > x > > subject to > 1/2 x' Pi x + qi' x + ri <= 0 for i=0..nq-1 > LBA <= A x <= UBA > LBX <= x <= UBX > > with : > H, Pi sparse (n x n) positive definite > g, qi dense (n x 1) > ri scalar > > n: number of decision variables (x) > nc: number of linear constraints (A) > nq: number of quadratic constraints > > > >If H, Pi is not positive-definite, the solver should throw an error. > >General information >=================== > > > >>Input scheme: casadi::QcqpSolverInput (QCQP_SOLVER_NUM_IN = 12) [qcqpIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| QCQP_SOLVER_H | h | The square matrix H: | >| | | sparse, (n x n). Only | >| | | the lower triangular | >| | | part is actually used. | >| | | The matrix is assumed | >| | | to be symmetrical. | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_G | g | The vector g: dense, | >| | | (n x 1) . | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_P | p | The horizontal stack | >| | | of all Pi. Each Pi is | >| | | sparse (n x n). Only | >| | | the lower triangular | >| | | part is actually used. | >| | | The matrix is assumed | >| | | to be symmetrical. | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_Q | q | The vertical stack of | >| | | all qi: dense, (nq n x | >| | | 1) . | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_R | r | The vertical stack of | >| | | all scalars ri (nq x | >| | | 1) . | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_A | a | The matrix A: sparse, | >| | | (nc x n) - product | >| | | with x must be dense. | >| | | . | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_LBA | lba | dense, (nc x 1) | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_UBA | uba | dense, (nc x 1) | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_LBX | lbx | dense, (n x 1) | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_UBX | ubx | dense, (n x 1) | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_X0 | x0 | dense, (n x 1) | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_LAM_X0 | lam_x0 | dense | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::QcqpSolverOutput (QCQP_SOLVER_NUM_OUT = 4) [qcqpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| QCQP_SOLVER_X | x | The primal solution . | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_COST | cost | The optimal cost . | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_LAM_A | lam_a | The dual solution | >| | | corresponding to | >| | | linear bounds . | >+------------------------+------------------------+------------------------+ >| QCQP_SOLVER_LAM_X | lam_x | The dual solution | >| | | corresponding to | >| | | simple bounds . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- socp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >QcqpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >socp >---- > > > >Solve a QCQP with an SocpSolver > >Note: this implementation relies on Cholesky decomposition: Chol(H) = L -> H >= LL' with L lower triangular This requires Pi, H to be positive definite. >Positive semi-definite is not sufficient. Notably, H==0 will not work. > >A better implementation would rely on matrix square root, but we need >singular value decomposition to implement that. > >This implementation makes use of the epigraph reformulation: > >:: > > * min f(x) > * x > * > * min t > * x, t f(x) <= t > * > > > >This implementation makes use of the following identity: > >:: > > * || Gx+h||_2 <= e'x + f > * > * x'(G'G - ee')x + (2 h'G - 2 f e') x + h'h - f <= 0 > * > >where we put e = [0 0 ... 1] for the quadratic constraint arising from the >epigraph reformulation and e==0 for all other quadratic constraints. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| socp_solver | OT_STRING | GenericType() | The SocpSolver | >| | | | used to solve | >| | | | the QCQPs. | >+-----------------+-----------------+-----------------+-----------------+ >| socp_solver_opt | OT_DICTIONARY | GenericType() | Options to be | >| ions | | | passed to the | >| | | | SOCPSOlver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+-------------------+ >| Id | >+===================+ >| socp_solver_stats | >+-------------------+ > >-------------------------------------------------------------------------------- > > > >Joris Gillis >Diagrams >-------- > > > >C++ includes: qcqp_solver.hpp -} newtype QcqpSolver = QcqpSolver (ForeignPtr QcqpSolver') -- typeclass decl class QcqpSolverClass a where castQcqpSolver :: a -> QcqpSolver instance QcqpSolverClass QcqpSolver where castQcqpSolver = id -- baseclass instances instance FunctionClass QcqpSolver where castFunction (QcqpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass QcqpSolver where castOptionsFunctionality (QcqpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass QcqpSolver where castPrintableObject (QcqpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass QcqpSolver where castSharedObject (QcqpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass QcqpSolver where castIOInterfaceFunction (QcqpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal QcqpSolver (Ptr QcqpSolver') where marshal (QcqpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (QcqpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__QcqpSolver" c_delete_casadi__QcqpSolver :: FunPtr (Ptr QcqpSolver' -> IO ()) instance WrapReturn (Ptr QcqpSolver') QcqpSolver where wrapReturn = (fmap QcqpSolver) . (newForeignPtr c_delete_casadi__QcqpSolver) -- raw decl data QpSolver' -- data decl {-| >QpSolver. > >Solves the following strictly convex problem: > > > >:: > > min 1/2 x' H x + g' x > x > > subject to > LBA <= A x <= UBA > LBX <= x <= UBX > > with : > H sparse (n x n) positive definite > g dense (n x 1) > > n: number of decision variables (x) > nc: number of constraints (A) > > > >If H is not positive-definite, the solver should throw an error. > >General information >=================== > > > >>Input scheme: casadi::QpSolverInput (QP_SOLVER_NUM_IN = 9) [qpIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| QP_SOLVER_H | h | The square matrix H: | >| | | sparse, (n x n). Only | >| | | the lower triangular | >| | | part is actually used. | >| | | The matrix is assumed | >| | | to be symmetrical. | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_G | g | The vector g: dense, | >| | | (n x 1) . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_A | a | The matrix A: sparse, | >| | | (nc x n) - product | >| | | with x must be dense. | >| | | . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_LBA | lba | dense, (nc x 1) | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_UBA | uba | dense, (nc x 1) | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_LBX | lbx | dense, (n x 1) | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_UBX | ubx | dense, (n x 1) | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_X0 | x0 | dense, (n x 1) | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_LAM_X0 | lam_x0 | dense | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::QpSolverOutput (QP_SOLVER_NUM_OUT = 4) [qpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| QP_SOLVER_X | x | The primal solution . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_COST | cost | The optimal cost . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_LAM_A | lam_a | The dual solution | >| | | corresponding to | >| | | linear bounds . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_LAM_X | lam_x | The dual solution | >| | | corresponding to | >| | | simple bounds . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- cplex > >- ooqp > >- qpoases > >- sqic > >- nlp > >- qcqp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >QpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >cplex >----- > > > >Interface to Cplex solver for sparse Quadratic Programs > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| barrier_maxiter | OT_INTEGER | 2.100e+09 | Maximum number | >| | | | of barrier | >| | | | iterations. | >+-----------------+-----------------+-----------------+-----------------+ >| convex | OT_BOOLEAN | true | Indicates if | >| | | | the QP is | >| | | | convex or not | >| | | | (affects only | >| | | | the barrier | >| | | | method). | >+-----------------+-----------------+-----------------+-----------------+ >| dep_check | OT_STRING | "off" | Detect | >| | | | redundant | >| | | | constraints. (a | >| | | | utomatic:-1|off | >| | | | :0|begin:1|end: | >| | | | 2|both:3) | >+-----------------+-----------------+-----------------+-----------------+ >| dump_filename | OT_STRING | "qp.dat" | The filename to | >| | | | dump to. | >+-----------------+-----------------+-----------------+-----------------+ >| dump_to_file | OT_BOOLEAN | false | Dumps QP to | >| | | | file in CPLEX | >| | | | format. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_method | OT_STRING | "automatic" | Determines | >| | | | which CPLEX | >| | | | algorithm to | >| | | | use. (automatic | >| | | | |primal_simplex | >| | | | |dual_simplex|n | >| | | | etwork|barrier| | >| | | | sifting|concurr | >| | | | ent|crossover) | >+-----------------+-----------------+-----------------+-----------------+ >| simplex_maxiter | OT_INTEGER | 2.100e+09 | Maximum number | >| | | | of simplex | >| | | | iterations. | >+-----------------+-----------------+-----------------+-----------------+ >| tol | OT_REAL | 0.000 | Tolerance of | >| | | | solver | >+-----------------+-----------------+-----------------+-----------------+ >| warm_start | OT_BOOLEAN | false | Use warm start | >| | | | with simplex | >| | | | methods | >| | | | (affects only | >| | | | the simplex | >| | | | methods). | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >ooqp >---- > > > >Interface to the OOQP Solver for quadratic programming The current >implementation assumes that OOQP is configured with the MA27 sparse linear >solver. > >NOTE: when doing multiple calls to evaluate(), check if you need to >reInit(); > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| artol | OT_REAL | 0.000 | tolerance as | >| | | | provided with | >| | | | setArTol to | >| | | | OOQP | >+-----------------+-----------------+-----------------+-----------------+ >| mutol | OT_REAL | 0.000 | tolerance as | >| | | | provided with | >| | | | setMuTol to | >| | | | OOQP | >+-----------------+-----------------+-----------------+-----------------+ >| print_level | OT_INTEGER | 0 | Print level. | >| | | | OOQP listens to | >| | | | print_level 0, | >| | | | 10 and 100 | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >qpoases >------- > > > >Interface to QPOases Solver for quadratic programming > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| CPUtime | OT_REAL | None | The maximum | >| | | | allowed CPU | >| | | | time in seconds | >| | | | for the whole | >| | | | initialisation | >| | | | (and the | >| | | | actually | >| | | | required one on | >| | | | output). | >| | | | Disabled if | >| | | | unset. | >+-----------------+-----------------+-----------------+-----------------+ >| boundRelaxation | OT_REAL | 10000 | Initial | >| | | | relaxation of | >| | | | bounds to start | >| | | | homotopy and | >| | | | initial value | >| | | | for far bounds. | >+-----------------+-----------------+-----------------+-----------------+ >| boundTolerance | OT_REAL | 0.000 | If upper and | >| | | | lower bounds | >| | | | differ less | >| | | | than this | >| | | | tolerance, they | >| | | | are regarded | >| | | | equal, i.e. as | >| | | | equality | >| | | | constraint. | >+-----------------+-----------------+-----------------+-----------------+ >| enableCholeskyR | OT_INTEGER | 0 | Specifies the | >| efactorisation | | | frequency of a | >| | | | full re- | >| | | | factorisation | >| | | | of projected | >| | | | Hessian matrix: | >| | | | 0: turns them | >| | | | off, 1: uses | >| | | | them at each | >| | | | iteration etc. | >+-----------------+-----------------+-----------------+-----------------+ >| enableDriftCorr | OT_INTEGER | 1 | Specifies the | >| ection | | | frequency of | >| | | | drift | >| | | | corrections: 0: | >| | | | turns them off. | >+-----------------+-----------------+-----------------+-----------------+ >| enableEqualitie | OT_BOOLEAN | False | Specifies | >| s | | | whether | >| | | | equalities | >| | | | should be | >| | | | treated as | >| | | | always active | >| | | | (True) or not | >| | | | (False) | >+-----------------+-----------------+-----------------+-----------------+ >| enableFarBounds | OT_BOOLEAN | True | Enables the use | >| | | | of far bounds. | >+-----------------+-----------------+-----------------+-----------------+ >| enableFlippingB | OT_BOOLEAN | True | Enables the use | >| ounds | | | of flipping | >| | | | bounds. | >+-----------------+-----------------+-----------------+-----------------+ >| enableFullLITes | OT_BOOLEAN | False | Enables | >| ts | | | condition- | >| | | | hardened (but | >| | | | more expensive) | >| | | | LI test. | >+-----------------+-----------------+-----------------+-----------------+ >| enableNZCTests | OT_BOOLEAN | True | Enables nonzero | >| | | | curvature | >| | | | tests. | >+-----------------+-----------------+-----------------+-----------------+ >| enableRamping | OT_BOOLEAN | True | Enables | >| | | | ramping. | >+-----------------+-----------------+-----------------+-----------------+ >| enableRegularis | OT_BOOLEAN | False | Enables | >| ation | | | automatic | >| | | | Hessian | >| | | | regularisation. | >+-----------------+-----------------+-----------------+-----------------+ >| epsDen | OT_REAL | 0.000 | Denominator | >| | | | tolerance for | >| | | | ratio tests. | >+-----------------+-----------------+-----------------+-----------------+ >| epsFlipping | OT_REAL | 0.000 | Tolerance of | >| | | | squared | >| | | | Cholesky | >| | | | diagonal factor | >| | | | which triggers | >| | | | flipping bound. | >+-----------------+-----------------+-----------------+-----------------+ >| epsIterRef | OT_REAL | 0.000 | Early | >| | | | termination | >| | | | tolerance for | >| | | | iterative | >| | | | refinement. | >+-----------------+-----------------+-----------------+-----------------+ >| epsLITests | OT_REAL | 0.000 | Tolerance for | >| | | | linear | >| | | | independence | >| | | | tests. | >+-----------------+-----------------+-----------------+-----------------+ >| epsNZCTests | OT_REAL | 0.000 | Tolerance for | >| | | | nonzero | >| | | | curvature | >| | | | tests. | >+-----------------+-----------------+-----------------+-----------------+ >| epsNum | OT_REAL | -0.000 | Numerator | >| | | | tolerance for | >| | | | ratio tests. | >+-----------------+-----------------+-----------------+-----------------+ >| epsRegularisati | OT_REAL | 0.000 | Scaling factor | >| on | | | of identity | >| | | | matrix used for | >| | | | Hessian | >| | | | regularisation. | >+-----------------+-----------------+-----------------+-----------------+ >| finalRamping | OT_REAL | 1 | Final value for | >| | | | ramping | >| | | | strategy. | >+-----------------+-----------------+-----------------+-----------------+ >| growFarBounds | OT_REAL | 1000 | Factor to grow | >| | | | far bounds. | >+-----------------+-----------------+-----------------+-----------------+ >| initialFarBound | OT_REAL | 1000000 | Initial size | >| s | | | for far bounds. | >+-----------------+-----------------+-----------------+-----------------+ >| initialRamping | OT_REAL | 0.500 | Start value for | >| | | | ramping | >| | | | strategy. | >+-----------------+-----------------+-----------------+-----------------+ >| initialStatusBo | OT_STRING | lower | Initial status | >| unds | | | of bounds at | >| | | | first | >| | | | iteration. | >+-----------------+-----------------+-----------------+-----------------+ >| maxDualJump | OT_REAL | 100000000 | Maximum allowed | >| | | | jump in dual | >| | | | variables in | >| | | | linear | >| | | | independence | >| | | | tests. | >+-----------------+-----------------+-----------------+-----------------+ >| maxPrimalJump | OT_REAL | 100000000 | Maximum allowed | >| | | | jump in primal | >| | | | variables in | >| | | | nonzero | >| | | | curvature | >| | | | tests. | >+-----------------+-----------------+-----------------+-----------------+ >| nWSR | OT_INTEGER | None | The maximum | >| | | | number of | >| | | | working set | >| | | | recalculations | >| | | | to be performed | >| | | | during the | >| | | | initial | >| | | | homotopy. | >| | | | Default is 5(nx | >| | | | + nc) | >+-----------------+-----------------+-----------------+-----------------+ >| numRefinementSt | OT_INTEGER | 1 | Maximum number | >| eps | | | of iterative | >| | | | refinement | >| | | | steps. | >+-----------------+-----------------+-----------------+-----------------+ >| numRegularisati | OT_INTEGER | 0 | Maximum number | >| onSteps | | | of successive | >| | | | regularisation | >| | | | steps. | >+-----------------+-----------------+-----------------+-----------------+ >| printLevel | OT_STRING | medium | Defines the | >| | | | amount of text | >| | | | output during | >| | | | QP solution, | >| | | | see Section 5.7 | >+-----------------+-----------------+-----------------+-----------------+ >| terminationTole | OT_REAL | 0.000 | Relative | >| rance | | | termination | >| | | | tolerance to | >| | | | stop homotopy. | >+-----------------+-----------------+-----------------+-----------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >sqic >---- > > > >Interface to the SQIC solver for quadratic programming > >>List of available options > >+----+------+---------+-------------+ >| Id | Type | Default | Description | >+====+======+=========+=============+ >+----+------+---------+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >nlp >--- > > > >Solve QPs using an NlpSolver > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| nlp_solver | OT_STRING | GenericType() | The NLPSOlver | >| | | | used to solve | >| | | | the QPs. | >+-----------------+-----------------+-----------------+-----------------+ >| nlp_solver_opti | OT_DICTIONARY | GenericType() | Options to be | >| ons | | | passed to the | >| | | | NLPSOlver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+------------------+ >| Id | >+==================+ >| nlp_solver_stats | >+------------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >qcqp >---- > > > >Solve QP using a QcqpSolver > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| qcqp_solver | OT_STRING | GenericType() | The QcqpSolver | >| | | | used to solve | >| | | | the QPs. | >+-----------------+-----------------+-----------------+-----------------+ >| qcqp_solver_opt | OT_DICTIONARY | GenericType() | Options to be | >| ions | | | passed to the | >| | | | QCQPSOlver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+-------------------+ >| Id | >+===================+ >| qcqp_solver_stats | >+-------------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: qp_solver.hpp -} newtype QpSolver = QpSolver (ForeignPtr QpSolver') -- typeclass decl class QpSolverClass a where castQpSolver :: a -> QpSolver instance QpSolverClass QpSolver where castQpSolver = id -- baseclass instances instance FunctionClass QpSolver where castFunction (QpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass QpSolver where castOptionsFunctionality (QpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass QpSolver where castPrintableObject (QpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass QpSolver where castSharedObject (QpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass QpSolver where castIOInterfaceFunction (QpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal QpSolver (Ptr QpSolver') where marshal (QpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (QpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__QpSolver" c_delete_casadi__QpSolver :: FunPtr (Ptr QpSolver' -> IO ()) instance WrapReturn (Ptr QpSolver') QpSolver where wrapReturn = (fmap QpSolver) . (newForeignPtr c_delete_casadi__QpSolver) -- raw decl data SX' -- data decl {-| -} newtype SX = SX (ForeignPtr SX') -- typeclass decl class SXClass a where castSX :: a -> SX instance SXClass SX where castSX = id -- baseclass instances instance PrintableObjectClass SX where castPrintableObject (SX x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SX (Ptr SX') where marshal (SX x) = return (unsafeForeignPtrToPtr x) marshalFree (SX x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SX" c_delete_casadi__SX :: FunPtr (Ptr SX' -> IO ()) instance WrapReturn (Ptr SX') SX where wrapReturn = (fmap SX) . (newForeignPtr c_delete_casadi__SX) -- raw decl data SXElement' -- data decl {-| -} newtype SXElement = SXElement (ForeignPtr SXElement') -- typeclass decl class SXElementClass a where castSXElement :: a -> SXElement instance SXElementClass SXElement where castSXElement = id -- baseclass instances -- helper instances instance Marshal SXElement (Ptr SXElement') where marshal (SXElement x) = return (unsafeForeignPtrToPtr x) marshalFree (SXElement x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SXElement" c_delete_casadi__SXElement :: FunPtr (Ptr SXElement' -> IO ()) instance WrapReturn (Ptr SXElement') SXElement where wrapReturn = (fmap SXElement) . (newForeignPtr c_delete_casadi__SXElement) -- raw decl data SXFunction' -- data decl {-| >Dynamically created function that can be expanded into a series of scalar >operations. > >Joel Andersson > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| just_in_time | OT_BOOLEAN | false | Just-in-time | casadi::SXFu | >| _opencl | | | compilation | nctionIntern | >| | | | for numeric | al | >| | | | evaluation | | >| | | | using OpenCL | | >| | | | (experimenta | | >| | | | l) | | >+--------------+--------------+--------------+--------------+--------------+ >| just_in_time | OT_BOOLEAN | false | Propagate | casadi::SXFu | >| _sparsity | | | sparsity | nctionIntern | >| | | | patterns | al | >| | | | using just- | | >| | | | in-time | | >| | | | compilation | | >| | | | to a CPU or | | >| | | | GPU using | | >| | | | OpenCL | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >Diagrams >-------- > > > >C++ includes: sx_function.hpp -} newtype SXFunction = SXFunction (ForeignPtr SXFunction') -- typeclass decl class SXFunctionClass a where castSXFunction :: a -> SXFunction instance SXFunctionClass SXFunction where castSXFunction = id -- baseclass instances instance FunctionClass SXFunction where castFunction (SXFunction x) = Function (castForeignPtr x) instance OptionsFunctionalityClass SXFunction where castOptionsFunctionality (SXFunction x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass SXFunction where castPrintableObject (SXFunction x) = PrintableObject (castForeignPtr x) instance SharedObjectClass SXFunction where castSharedObject (SXFunction x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass SXFunction where castIOInterfaceFunction (SXFunction x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SXFunction (Ptr SXFunction') where marshal (SXFunction x) = return (unsafeForeignPtrToPtr x) marshalFree (SXFunction x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SXFunction" c_delete_casadi__SXFunction :: FunPtr (Ptr SXFunction' -> IO ()) instance WrapReturn (Ptr SXFunction') SXFunction where wrapReturn = (fmap SXFunction) . (newForeignPtr c_delete_casadi__SXFunction) -- raw decl data SdpSolver' -- data decl {-| >SdpSolver. > >Solves an SDP problem in standard form. >Seehttp://sdpa.indsys.chuo-u.ac.jp/sdpa/files/sdpa-c.6.2.0.manual.pdf > >Primal: > > > >:: > > min c' x > x > subject to > P = Sum_i^m F_i x_i - G > P negative semidefinite > > LBA <= A x <= UBA > LBX <= x <= UBX > > with x ( n x 1) > c ( n x 1 ) > G, F_i sparse symmetric (m x m) > X dense symmetric ( m x m ) > A sparse matrix ( nc x n) > LBA, UBA dense vector (nc x 1) > LBX, UBX dense vector (n x 1) > > > >This formulation is chosen as primal, because it does not call for a large >decision variable space. > >Dual: > > > >:: > > max trace(G Y) > Y > > subject to > trace(F_i Y) = c_i > Y positive semidefinite > > with Y dense symmetric ( m x m) > > > >On generality: you might have formulation with block partitioning: > >Primal: > > > >:: > > min c' x > x > subject to > Pj = Sum_i^m F_ij x_i - gj for all j > Pj negative semidefinite for all j > > with x ( n x 1) > c ( n x 1 ) > G, F_i sparse symmetric (m x m) > X dense symmetric ( m x m ) > > > >Dual: > >:: > > max Sum_j trace(Gj Yj) > Yj > > subject to > Sum_j trace(F_ij Yj) = c_i for all j > Yj positive semidefinite for all j > > with Y dense symmetric ( m x m) > > > >You can cast this into the standard form with: G = blkdiag(Gj for all j) Fi >= blkdiag(F_ij for all j) > >Implementations of SdpSolver are encouraged to exploit this block structure. > >General information >=================== > > > >>Input scheme: casadi::SDPInput (SDP_SOLVER_NUM_IN = 8) [sdpIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| SDP_SOLVER_F | f | The horizontal stack | >| | | of all matrices F_i: ( | >| | | m x nm) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_C | c | The vector c: ( n x 1) | >| | | . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_G | g | The matrix G: ( m x m) | >| | | . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_A | a | The matrix A: ( nc x | >| | | n) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_LBA | lba | Lower bounds on Ax ( | >| | | nc x 1) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_UBA | uba | Upper bounds on Ax ( | >| | | nc x 1) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_LBX | lbx | Lower bounds on x ( n | >| | | x 1 ) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_UBX | ubx | Upper bounds on x ( n | >| | | x 1 ) . | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::SDPOutput (SDP_SOLVER_NUM_OUT = 7) [sdpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| SDP_SOLVER_X | x | The primal solution (n | >| | | x 1) - may be used as | >| | | initial guess . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_P | p | The solution P (m x m) | >| | | - may be used as | >| | | initial guess . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_DUAL | dual | The dual solution (m x | >| | | m) - may be used as | >| | | initial guess . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_COST | cost | The primal optimal | >| | | cost (1 x 1) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_DUAL_COST | dual_cost | The dual optimal cost | >| | | (1 x 1) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_LAM_A | lam_a | The dual solution | >| | | corresponding to the | >| | | linear constraints (nc | >| | | x 1) . | >+------------------------+------------------------+------------------------+ >| SDP_SOLVER_LAM_X | lam_x | The dual solution | >| | | corresponding to | >| | | simple bounds (n x 1) | >| | | . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| calc_dual | OT_BOOLEAN | true | Indicate if | casadi::SdpS | >| | | | dual should | olverInterna | >| | | | be allocated | l | >| | | | and | | >| | | | calculated. | | >| | | | You may want | | >| | | | to avoid | | >| | | | calculating | | >| | | | this | | >| | | | variable for | | >| | | | problems | | >| | | | with n | | >| | | | large, as is | | >| | | | always dense | | >| | | | (m x m). | | >+--------------+--------------+--------------+--------------+--------------+ >| calc_p | OT_BOOLEAN | true | Indicate if | casadi::SdpS | >| | | | the P-part | olverInterna | >| | | | of primal | l | >| | | | solution | | >| | | | should be | | >| | | | allocated | | >| | | | and | | >| | | | calculated. | | >| | | | You may want | | >| | | | to avoid | | >| | | | calculating | | >| | | | this | | >| | | | variable for | | >| | | | problems | | >| | | | with n | | >| | | | large, as is | | >| | | | always dense | | >| | | | (m x m). | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| print_proble | OT_BOOLEAN | false | Print out | casadi::SdpS | >| m | | | problem | olverInterna | >| | | | statement | l | >| | | | for | | >| | | | debugging. | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- dsdp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >SdpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >dsdp >---- > > > >Interface to the SDP solver DSDP Warning: The solver DSDP is not good at >handling linear equalities. There are several options if you notice >difficulties: play around with the parameter "_penalty" leave a gap >manually switch to another SDP Solver > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| _loglevel | OT_INTEGER | 0 | An integer that | >| | | | specifies how | >| | | | much logging is | >| | | | done on stdout. | >+-----------------+-----------------+-----------------+-----------------+ >| _penalty | OT_REAL | 100000 | Penality | >| | | | parameter | >| | | | lambda. Must | >| | | | exceed the | >| | | | trace of Y. | >| | | | This parameter | >| | | | heavily | >| | | | influences the | >| | | | ability of DSDP | >| | | | to treat linear | >| | | | equalities. The | >| | | | DSDP standard | >| | | | default (1e8) | >| | | | will make a | >| | | | problem with | >| | | | linear equality | >| | | | return unusable | >| | | | solutions. | >+-----------------+-----------------+-----------------+-----------------+ >| _printlevel | OT_INTEGER | 1 | A printlevel of | >| | | | zero will | >| | | | disable all | >| | | | output. Another | >| | | | number | >| | | | indicates how | >| | | | often a line is | >| | | | printed. | >+-----------------+-----------------+-----------------+-----------------+ >| _reuse | OT_INTEGER | 4 | Maximum on the | >| | | | number of times | >| | | | the Schur | >| | | | complement | >| | | | matrix is | >| | | | reused | >+-----------------+-----------------+-----------------+-----------------+ >| _rho | OT_REAL | 4 | Potential | >| | | | parameter. Must | >| | | | be >=1 | >+-----------------+-----------------+-----------------+-----------------+ >| _use_penalty | OT_BOOLEAN | true | Modifies the | >| | | | algorithm to | >| | | | use a penality | >| | | | gamma on r. | >+-----------------+-----------------+-----------------+-----------------+ >| _zbar | OT_REAL | 1.000e+10 | Initial upper | >| | | | bound on the | >| | | | objective of | >| | | | the dual | >| | | | problem. | >+-----------------+-----------------+-----------------+-----------------+ >| dualTol | OT_REAL | 0.000 | Tolerance for | >| | | | dual | >| | | | infeasibility | >| | | | (translates to | >| | | | primal | >| | | | infeasibility | >| | | | in dsdp terms) | >+-----------------+-----------------+-----------------+-----------------+ >| gapTol | OT_REAL | 0.000 | Convergence | >| | | | criterion based | >| | | | on distance | >| | | | between primal | >| | | | and dual | >| | | | objective | >+-----------------+-----------------+-----------------+-----------------+ >| inf | OT_REAL | 1.000e+30 | Treat numbers | >| | | | higher than | >| | | | this as | >| | | | infinity | >+-----------------+-----------------+-----------------+-----------------+ >| maxIter | OT_INTEGER | 500 | Maximum number | >| | | | of iterations | >+-----------------+-----------------+-----------------+-----------------+ >| primalTol | OT_REAL | 0.000 | Tolerance for | >| | | | primal | >| | | | infeasibility | >| | | | (translates to | >| | | | dual | >| | | | infeasibility | >| | | | in dsdp terms) | >+-----------------+-----------------+-----------------+-----------------+ >| stepTol | OT_REAL | 0.050 | Terminate the | >| | | | solver if the | >| | | | step length in | >| | | | the primal is | >| | | | below this | >| | | | tolerance. | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+--------------------+ >| Id | >+====================+ >| solution_type | >+--------------------+ >| termination_reason | >+--------------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: sdp_solver.hpp -} newtype SdpSolver = SdpSolver (ForeignPtr SdpSolver') -- typeclass decl class SdpSolverClass a where castSdpSolver :: a -> SdpSolver instance SdpSolverClass SdpSolver where castSdpSolver = id -- baseclass instances instance FunctionClass SdpSolver where castFunction (SdpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass SdpSolver where castOptionsFunctionality (SdpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass SdpSolver where castPrintableObject (SdpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass SdpSolver where castSharedObject (SdpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass SdpSolver where castIOInterfaceFunction (SdpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SdpSolver (Ptr SdpSolver') where marshal (SdpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SdpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SdpSolver" c_delete_casadi__SdpSolver :: FunPtr (Ptr SdpSolver' -> IO ()) instance WrapReturn (Ptr SdpSolver') SdpSolver where wrapReturn = (fmap SdpSolver) . (newForeignPtr c_delete_casadi__SdpSolver) -- raw decl data SdqpSolver' -- data decl {-| >SdqpSolver. > >Same as an SdpSolver, but with a quadratic objective 1/2 x' H x > >General information >=================== > > > >>Input scheme: casadi::SDQPInput (SDQP_SOLVER_NUM_IN = 9) [sdqpIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| SDQP_SOLVER_H | h | The matrix H: sparse ( | >| | | n x n) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_C | c | The vector c: ( n x 1) | >| | | . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_F | f | The horizontal stack | >| | | of all matrices F_i: ( | >| | | m x nm) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_G | g | The matrix G: ( m x m) | >| | | . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_A | a | The matrix A: ( nc x | >| | | n) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_LBA | lba | Lower bounds on Ax ( | >| | | nc x 1) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_UBA | uba | Upper bounds on Ax ( | >| | | nc x 1) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_LBX | lbx | Lower bounds on x ( n | >| | | x 1 ) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_UBX | ubx | Upper bounds on x ( n | >| | | x 1 ) . | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::SDQPOutput (SDQP_SOLVER_NUM_OUT = 7) [sdqpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| SDQP_SOLVER_X | x | The primal solution (n | >| | | x 1) - may be used as | >| | | initial guess . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_P | p | The solution P (m x m) | >| | | - may be used as | >| | | initial guess . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_DUAL | dual | The dual solution (m x | >| | | m) - may be used as | >| | | initial guess . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_COST | cost | The primal optimal | >| | | cost (1 x 1) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_DUAL_COST | dual_cost | The dual optimal cost | >| | | (1 x 1) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_LAM_A | lam_a | The dual solution | >| | | corresponding to the | >| | | linear constraints (nc | >| | | x 1) . | >+------------------------+------------------------+------------------------+ >| SDQP_SOLVER_LAM_X | lam_x | The dual solution | >| | | corresponding to | >| | | simple bounds (n x 1) | >| | | . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| sdp_solver | OT_STRING | GenericType( | The | casadi::Sdqp | >| | | ) | SdqpSolver | SolverIntern | >| | | | used to | al | >| | | | solve the | | >| | | | SDPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| sdp_solver_o | OT_DICTIONAR | GenericType( | Options to | casadi::Sdqp | >| ptions | Y | ) | be passed to | SolverIntern | >| | | | the | al | >| | | | SDPSOlver | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- sdp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >SdqpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >sdp >--- > > > >Solve an SQDP using an SdpSolver Note: this implementation relies on >Cholesky decomposition: Chol(H) = L -> H = LL' with L lower triangular This >requires Pi, H to be positive definite. Positive semi-definite is not >sufficient. Notably, H==0 will not work. > >A better implementation would rely on matrix square root, but we need >singular value decomposition to implement that. > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| sdp_solver | OT_STRING | GenericType() | The SdpSolver | >| | | | used to solve | >| | | | the SDQPs. | >+-----------------+-----------------+-----------------+-----------------+ >| sdp_solver_opti | OT_DICTIONARY | GenericType() | Options to be | >| ons | | | passed to the | >| | | | SDPSOlver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+------------------+ >| Id | >+==================+ >| sdp_solver_stats | >+------------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: sdqp_solver.hpp -} newtype SdqpSolver = SdqpSolver (ForeignPtr SdqpSolver') -- typeclass decl class SdqpSolverClass a where castSdqpSolver :: a -> SdqpSolver instance SdqpSolverClass SdqpSolver where castSdqpSolver = id -- baseclass instances instance FunctionClass SdqpSolver where castFunction (SdqpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass SdqpSolver where castOptionsFunctionality (SdqpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass SdqpSolver where castPrintableObject (SdqpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass SdqpSolver where castSharedObject (SdqpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass SdqpSolver where castIOInterfaceFunction (SdqpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SdqpSolver (Ptr SdqpSolver') where marshal (SdqpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SdqpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SdqpSolver" c_delete_casadi__SdqpSolver :: FunPtr (Ptr SdqpSolver' -> IO ()) instance WrapReturn (Ptr SdqpSolver') SdqpSolver where wrapReturn = (fmap SdqpSolver) . (newForeignPtr c_delete_casadi__SdqpSolver) -- raw decl data SharedObject' -- data decl {-| >SharedObject implements a reference counting framework similar for efficient >and easily-maintained memory management. > >To use the class, both the SharedObject class (the public class), and the >SharedObjectNode class (the internal class) must be inherited from. It can >be done in two different files and together with memory management, this >approach provides a clear distinction of which methods of the class are to >be considered "public", i.e. methods for public use that can be considered >to remain over time with small changes, and the internal memory. > >When interfacing a software, which typically includes including some header >file, this is best done only in the file where the internal class is >defined, to avoid polluting the global namespace and other side effects. > >The default constructor always means creating a null pointer to an internal >class only. To allocate an internal class (this works only when the internal >class isn't abstract), use the constructor with arguments. > >The copy constructor and the assignment operator perform shallow copies >only, to make a deep copy you must use the clone method explicitly. This >will give a shared pointer instance. > >In an inheritance hierarchy, you can cast down automatically, e.g. ( >SXFunction is a child class of Function): SXFunction derived(...); Function >base = derived; > >To cast up, use the shared_cast template function, which works analogously >to dynamic_cast, static_cast, const_cast etc, e.g.: SXFunction derived(...); >Function base = derived; SXFunction derived_from_base = >shared_cast(base); > >A failed shared_cast will result in a null pointer (cf. dynamic_cast) > >Joel Andersson > >C++ includes: shared_object.hpp -} newtype SharedObject = SharedObject (ForeignPtr SharedObject') -- typeclass decl class SharedObjectClass a where castSharedObject :: a -> SharedObject instance SharedObjectClass SharedObject where castSharedObject = id -- baseclass instances instance PrintableObjectClass SharedObject where castPrintableObject (SharedObject x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SharedObject (Ptr SharedObject') where marshal (SharedObject x) = return (unsafeForeignPtrToPtr x) marshalFree (SharedObject x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SharedObject" c_delete_casadi__SharedObject :: FunPtr (Ptr SharedObject' -> IO ()) instance WrapReturn (Ptr SharedObject') SharedObject where wrapReturn = (fmap SharedObject) . (newForeignPtr c_delete_casadi__SharedObject) -- raw decl data Simulator' -- data decl {-| >Integrator class. > >An "simulator" integrates an IVP, stopping at a (fixed) number of grid >points and evaluates a set of output functions at these points. The internal >stepsizes of the integrator need not coincide with the gridpoints. > >Simulator is an casadi::Function mapping from casadi::IntegratorInput to n. >\\\\ > >The output function needs to be a mapping from casadi::DAEInput to n. The >default output has n=1 and the output is the (vectorized) differential state >for each time step. > >Joel Andersson > >>Input scheme: casadi::IntegratorInput (INTEGRATOR_NUM_IN = 6) [integratorIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| INTEGRATOR_X0 | x0 | Differential state at | >| | | the initial time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_P | p | Parameters . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_Z0 | z0 | Initial guess for the | >| | | algebraic variable . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RX0 | rx0 | Backward differential | >| | | state at the final | >| | | time . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RP | rp | Backward parameter | >| | | vector . | >+------------------------+------------------------+------------------------+ >| INTEGRATOR_RZ0 | rz0 | Initial guess for the | >| | | backwards algebraic | >| | | variable . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | casadi::Simu | >| | | | uts) (initi | latorInterna | >| | | | al|step) | l | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available monitors > >+---------+---------------------------+ >| Id | Used in | >+=========+===========================+ >| initial | casadi::SimulatorInternal | >+---------+---------------------------+ >| inputs | casadi::FunctionInternal | >+---------+---------------------------+ >| outputs | casadi::FunctionInternal | >+---------+---------------------------+ >| step | casadi::SimulatorInternal | >+---------+---------------------------+ > >Diagrams >-------- > > > >C++ includes: simulator.hpp -} newtype Simulator = Simulator (ForeignPtr Simulator') -- typeclass decl class SimulatorClass a where castSimulator :: a -> Simulator instance SimulatorClass Simulator where castSimulator = id -- baseclass instances instance FunctionClass Simulator where castFunction (Simulator x) = Function (castForeignPtr x) instance OptionsFunctionalityClass Simulator where castOptionsFunctionality (Simulator x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass Simulator where castPrintableObject (Simulator x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Simulator where castSharedObject (Simulator x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass Simulator where castIOInterfaceFunction (Simulator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal Simulator (Ptr Simulator') where marshal (Simulator x) = return (unsafeForeignPtrToPtr x) marshalFree (Simulator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Simulator" c_delete_casadi__Simulator :: FunPtr (Ptr Simulator' -> IO ()) instance WrapReturn (Ptr Simulator') Simulator where wrapReturn = (fmap Simulator) . (newForeignPtr c_delete_casadi__Simulator) -- raw decl data Slice' -- data decl {-| >Class representing a Slice. > >Note that Python or Octave do not need to use this class. They can just use >slicing utility from the host language ( M[0:6] in Python, M(1:7) ) > >C++ includes: slice.hpp -} newtype Slice = Slice (ForeignPtr Slice') -- typeclass decl class SliceClass a where castSlice :: a -> Slice instance SliceClass Slice where castSlice = id -- baseclass instances instance PrintableObjectClass Slice where castPrintableObject (Slice x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal Slice (Ptr Slice') where marshal (Slice x) = return (unsafeForeignPtrToPtr x) marshalFree (Slice x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Slice" c_delete_casadi__Slice :: FunPtr (Ptr Slice' -> IO ()) instance WrapReturn (Ptr Slice') Slice where wrapReturn = (fmap Slice) . (newForeignPtr c_delete_casadi__Slice) -- raw decl data SocpSolver' -- data decl {-| >SocpSolver. > >Solves an Second Order Cone Programming (SOCP) problem in standard form. > >Primal: > > > >:: > > min c' x > x > subject to > || Gi' x + hi ||_2 <= ei' x + fi i = 1..m > > LBA <= A x <= UBA > LBX <= x <= UBX > > with x ( n x 1) > c ( n x 1 ) > Gi sparse (n x ni) > hi dense (ni x 1) > ei dense (n x 1) > fi dense (1 x 1) > N = Sum_i^m ni > A sparse (nc x n) > LBA, UBA dense vector (nc x 1) > LBX, UBX dense vector (n x 1) > > > >General information >=================== > > > >>Input scheme: casadi::SOCPInput (SOCP_SOLVER_NUM_IN = 10) [socpIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| SOCP_SOLVER_G | g | The horizontal stack | >| | | of all matrices Gi: ( | >| | | n x N) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_H | h | The vertical stack of | >| | | all vectors hi: ( N x | >| | | 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_E | e | The vertical stack of | >| | | all vectors ei: ( nm x | >| | | 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_F | f | The vertical stack of | >| | | all scalars fi: ( m x | >| | | 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_C | c | The vector c: ( n x 1) | >| | | . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_A | a | The matrix A: ( nc x | >| | | n) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_LBA | lba | Lower bounds on Ax ( | >| | | nc x 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_UBA | uba | Upper bounds on Ax ( | >| | | nc x 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_LBX | lbx | Lower bounds on x ( n | >| | | x 1 ) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_UBX | ubx | Upper bounds on x ( n | >| | | x 1 ) . | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::SOCPOutput (SOCP_SOLVER_NUM_OUT = 4) [socpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| SOCP_SOLVER_X | x | The primal solution (n | >| | | x 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_COST | cost | The primal optimal | >| | | cost (1 x 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_LAM_A | lam_a | The dual solution | >| | | corresponding to the | >| | | linear constraints (nc | >| | | x 1) . | >+------------------------+------------------------+------------------------+ >| SOCP_SOLVER_LAM_X | lam_x | The dual solution | >| | | corresponding to | >| | | simple bounds (n x 1) | >| | | . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| ni | OT_INTEGERVE | GenericType( | Provide the | casadi::Socp | >| | CTOR | ) | size of each | SolverIntern | >| | | | SOC | al | >| | | | constraint. | | >| | | | Must sum up | | >| | | | to N. | | >+--------------+--------------+--------------+--------------+--------------+ >| print_proble | OT_BOOLEAN | false | Print out | casadi::Socp | >| m | | | problem | SolverIntern | >| | | | statement | al | >| | | | for | | >| | | | debugging. | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- sdp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >SocpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >sdp >--- > > > >Solve SOCPs using an SdpSolver > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| sdp_solver | OT_STRING | GenericType() | The SdpSolver | >| | | | used to solve | >| | | | the SOCPs. | >+-----------------+-----------------+-----------------+-----------------+ >| sdp_solver_opti | OT_DICTIONARY | GenericType() | Options to be | >| ons | | | passed to the | >| | | | SDPSOlver | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+------------------+ >| Id | >+==================+ >| sdp_solver_stats | >+------------------+ > >-------------------------------------------------------------------------------- > > > >Joris Gillis >Diagrams >-------- > > > >C++ includes: socp_solver.hpp -} newtype SocpSolver = SocpSolver (ForeignPtr SocpSolver') -- typeclass decl class SocpSolverClass a where castSocpSolver :: a -> SocpSolver instance SocpSolverClass SocpSolver where castSocpSolver = id -- baseclass instances instance FunctionClass SocpSolver where castFunction (SocpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass SocpSolver where castOptionsFunctionality (SocpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass SocpSolver where castPrintableObject (SocpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass SocpSolver where castSharedObject (SocpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass SocpSolver where castIOInterfaceFunction (SocpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SocpSolver (Ptr SocpSolver') where marshal (SocpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SocpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SocpSolver" c_delete_casadi__SocpSolver :: FunPtr (Ptr SocpSolver' -> IO ()) instance WrapReturn (Ptr SocpSolver') SocpSolver where wrapReturn = (fmap SocpSolver) . (newForeignPtr c_delete_casadi__SocpSolver) -- raw decl data Sparsity' -- data decl {-| >General sparsity class. > >The storage format is a compressed column storage (CCS) format. In this >format, the structural non-zero elements are stored in column-major order, >starting from the upper left corner of the matrix and ending in the lower >right corner. > >In addition to the dimension ( size1(), size2()), (i.e. the number of rows >and the number of columns respectively), there are also two vectors of >integers: > >"colind" [length size2()+1], which contains the index to the first non- >zero element on or after the corresponding column. All the non-zero elements >of a particular i are thus the elements with index el that fulfills: >colind[i] <= el < colind[i+1]. > >"row" [same length as the number of non-zero elements, size()] The rows >for each of the structural non-zeros. > >Note that with this format, it is cheap to loop over all the non-zero >elements of a particular column, at constant time per element, but expensive >to jump to access a location (i, j). > >If the matrix is dense, i.e. length(row) == size1()*size2(), the format >reduces to standard dense column major format, which allows access to an >arbitrary element in constant time. > >Since the object is reference counted (it inherits from SharedObject), >several matrices are allowed to share the same sparsity pattern. > >The implementations of some methods of this class has been taken from the >CSparse package and modified to use C++ standard library and CasADi data >structures. > >See: Matrix > >Joel Andersson > >C++ includes: sparsity.hpp -} newtype Sparsity = Sparsity (ForeignPtr Sparsity') -- typeclass decl class SparsityClass a where castSparsity :: a -> Sparsity instance SparsityClass Sparsity where castSparsity = id -- baseclass instances instance PrintableObjectClass Sparsity where castPrintableObject (Sparsity x) = PrintableObject (castForeignPtr x) instance SharedObjectClass Sparsity where castSharedObject (Sparsity x) = SharedObject (castForeignPtr x) -- helper instances instance Marshal Sparsity (Ptr Sparsity') where marshal (Sparsity x) = return (unsafeForeignPtrToPtr x) marshalFree (Sparsity x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__Sparsity" c_delete_casadi__Sparsity :: FunPtr (Ptr Sparsity' -> IO ()) instance WrapReturn (Ptr Sparsity') Sparsity where wrapReturn = (fmap Sparsity) . (newForeignPtr c_delete_casadi__Sparsity) -- raw decl data StabilizedQpSolver' -- data decl {-| >StabilizedQpSolver. > >Solves the following strictly convex problem: > > > >:: > > min 1/2 x' H x + g' x > x > > subject to > LBA <= A x <= UBA > LBX <= x <= UBX > > with : > H sparse (n x n) positive definite > g dense (n x 1) > > n: number of decision variables (x) > nc: number of constraints (A) > > > >If H is not positive-definite, the solver should throw an error. > >General information >=================== > > > >>Input scheme: casadi::StabilizedQpSolverInput (STABILIZED_QP_SOLVER_NUM_IN = 12) [stabilizedQpIn] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| STABILIZED_QP_SOLVER_H | h | The square matrix H: | >| | | sparse, (n x n). Only | >| | | the lower triangular | >| | | part is actually used. | >| | | The matrix is assumed | >| | | to be symmetrical. | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_G | g | The vector g: dense, | >| | | (n x 1) . | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_A | a | The matrix A: sparse, | >| | | (nc x n) - product | >| | | with x must be dense. | >| | | . | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_L | lba | dense, (nc x 1) | >| BA | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_U | uba | dense, (nc x 1) | >| BA | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_L | lbx | dense, (n x 1) | >| BX | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_U | ubx | dense, (n x 1) | >| BX | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_X | x0 | dense, (n x 1) | >| 0 | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_L | lam_x0 | dense | >| AM_X0 | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_M | muR | dense (1 x 1) | >| UR | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_M | muE | dense (nc x 1) | >| UE | | | >+------------------------+------------------------+------------------------+ >| STABILIZED_QP_SOLVER_M | mu | dense (nc x 1) | >| U | | | >+------------------------+------------------------+------------------------+ > >>Output scheme: casadi::QpSolverOutput (QP_SOLVER_NUM_OUT = 4) [qpOut] > >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| QP_SOLVER_X | x | The primal solution . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_COST | cost | The optimal cost . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_LAM_A | lam_a | The dual solution | >| | | corresponding to | >| | | linear bounds . | >+------------------------+------------------------+------------------------+ >| QP_SOLVER_LAM_X | lam_x | The dual solution | >| | | corresponding to | >| | | simple bounds . | >+------------------------+------------------------+------------------------+ > >>List of available options > >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| ad_mode | OT_STRING | "automatic" | How to | casadi::Func | >| | | | calculate | tionInternal | >| | | | the | | >| | | | Jacobians. | | >| | | | (forward: | | >| | | | only forward | | >| | | | mode|reverse | | >| | | | : only | | >| | | | adjoint mode | | >| | | | |automatic: | | >| | | | a heuristic | | >| | | | decides | | >| | | | which is | | >| | | | more | | >| | | | appropriate) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_g | OT_DERIVATIV | GenericType( | Function | casadi::Func | >| enerator | EGENERATOR | ) | that returns | tionInternal | >| | | | a derivative | | >| | | | function | | >| | | | given a | | >| | | | number of | | >| | | | forward and | | >| | | | reverse | | >| | | | directional | | >| | | | derivative, | | >| | | | overrides | | >| | | | internal | | >| | | | routines. | | >| | | | Check docume | | >| | | | ntation of D | | >| | | | erivativeGen | | >| | | | erator . | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | | >| | | | uts) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >List of plugins >=============== > > > >- sqic > >- qp > >Note: some of the plugins in this list might not be available on your >system. Also, there might be extra plugins available to you that are not >listed here. You can obtain their documentation with >StabilizedQpSolver.doc("myextraplugin") > > > >-------------------------------------------------------------------------------- > >sqic >---- > > > >Interface to SQIC > >>List of available options > >+----+------+---------+-------------+ >| Id | Type | Default | Description | >+====+======+=========+=============+ >+----+------+---------+-------------+ > >-------------------------------------------------------------------------------- > > > >-------------------------------------------------------------------------------- > >qp -- > > > >Solved a stabilized QP using a standard QP solver > >>List of available options > >+-----------------+-----------------+-----------------+-----------------+ >| Id | Type | Default | Description | >+=================+=================+=================+=================+ >| qp_solver | OT_STRING | GenericType() | The QP solver | >| | | | used to solve | >| | | | the stabilized | >| | | | QPs. | >+-----------------+-----------------+-----------------+-----------------+ >| qp_solver_optio | OT_DICTIONARY | GenericType() | Options to be | >| ns | | | passed to the | >| | | | QP solver | >| | | | instance | >+-----------------+-----------------+-----------------+-----------------+ > >>List of available stats > >+-----------------+ >| Id | >+=================+ >| qp_solver_stats | >+-----------------+ > >-------------------------------------------------------------------------------- > > > >Joel Andersson >Diagrams >-------- > > > >C++ includes: stabilized_qp_solver.hpp -} newtype StabilizedQpSolver = StabilizedQpSolver (ForeignPtr StabilizedQpSolver') -- typeclass decl class StabilizedQpSolverClass a where castStabilizedQpSolver :: a -> StabilizedQpSolver instance StabilizedQpSolverClass StabilizedQpSolver where castStabilizedQpSolver = id -- baseclass instances instance FunctionClass StabilizedQpSolver where castFunction (StabilizedQpSolver x) = Function (castForeignPtr x) instance OptionsFunctionalityClass StabilizedQpSolver where castOptionsFunctionality (StabilizedQpSolver x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass StabilizedQpSolver where castPrintableObject (StabilizedQpSolver x) = PrintableObject (castForeignPtr x) instance SharedObjectClass StabilizedQpSolver where castSharedObject (StabilizedQpSolver x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass StabilizedQpSolver where castIOInterfaceFunction (StabilizedQpSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal StabilizedQpSolver (Ptr StabilizedQpSolver') where marshal (StabilizedQpSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (StabilizedQpSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__StabilizedQpSolver" c_delete_casadi__StabilizedQpSolver :: FunPtr (Ptr StabilizedQpSolver' -> IO ()) instance WrapReturn (Ptr StabilizedQpSolver') StabilizedQpSolver where wrapReturn = (fmap StabilizedQpSolver) . (newForeignPtr c_delete_casadi__StabilizedQpSolver) -- raw decl data SymbolicNLP' -- data decl {-| >A symbolic NLP representation. > >Joel Andersson > >C++ includes: symbolic_nlp.hpp -} newtype SymbolicNLP = SymbolicNLP (ForeignPtr SymbolicNLP') -- typeclass decl class SymbolicNLPClass a where castSymbolicNLP :: a -> SymbolicNLP instance SymbolicNLPClass SymbolicNLP where castSymbolicNLP = id -- baseclass instances instance PrintableObjectClass SymbolicNLP where castPrintableObject (SymbolicNLP x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SymbolicNLP (Ptr SymbolicNLP') where marshal (SymbolicNLP x) = return (unsafeForeignPtrToPtr x) marshalFree (SymbolicNLP x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SymbolicNLP" c_delete_casadi__SymbolicNLP :: FunPtr (Ptr SymbolicNLP' -> IO ()) instance WrapReturn (Ptr SymbolicNLP') SymbolicNLP where wrapReturn = (fmap SymbolicNLP) . (newForeignPtr c_delete_casadi__SymbolicNLP) -- raw decl data IOInterfaceFunction' -- data decl {-| >Interface for accessing input and output data structures. > >Joel Andersson > >C++ includes: io_interface.hpp -} newtype IOInterfaceFunction = IOInterfaceFunction (ForeignPtr IOInterfaceFunction') -- typeclass decl class IOInterfaceFunctionClass a where castIOInterfaceFunction :: a -> IOInterfaceFunction instance IOInterfaceFunctionClass IOInterfaceFunction where castIOInterfaceFunction = id -- baseclass instances -- helper instances instance Marshal IOInterfaceFunction (Ptr IOInterfaceFunction') where marshal (IOInterfaceFunction x) = return (unsafeForeignPtrToPtr x) marshalFree (IOInterfaceFunction x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__IOInterface_casadi__Function_" c_delete_casadi__IOInterface_casadi__Function_ :: FunPtr (Ptr IOInterfaceFunction' -> IO ()) instance WrapReturn (Ptr IOInterfaceFunction') IOInterfaceFunction where wrapReturn = (fmap IOInterfaceFunction) . (newForeignPtr c_delete_casadi__IOInterface_casadi__Function_)