{-# 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 = 4) [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_INTEGRATO | GenericType( | An | casadi::Cont | >| | R | ) | 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. > >Joris Gillis > >>Input scheme: casadi::NLPSolverInput (NLP_SOLVER_NUM_IN = 9) [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 = 7) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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. > >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) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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_LINEARSOL | GenericType( | User-defined | casadi::Impl | >| r | VER | ) | 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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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. > >The class does not specify the method used for the integration. This is >defined in derived classes. > >Joel Andersson > >>Input scheme: casadi::IntegratorInput (INTEGRATOR_NUM_IN = 7) [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 = 7) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 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) > >Joris Gillis > >>Input scheme: casadi::LPSolverInput (LP_SOLVER_NUM_IN = 7) [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 = 5) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 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. Joel Andersson > >>Input scheme: casadi::LinsolInput (LINSOL_NUM_IN = 3) [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 = 2) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 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 > >Joel Andersson > >>Input scheme: casadi::NLPSolverInput (NLP_SOLVER_NUM_IN = 9) [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 = 7) [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::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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 = 14) [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 = 5) [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. > >Joris Gillis > >>Input scheme: casadi::QCQPSolverInput (QCQP_SOLVER_NUM_IN = 13) [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 = 5) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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. > >Joel Andersson > >>Input scheme: casadi::QPSolverInput (QP_SOLVER_NUM_IN = 10) [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 = 5) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 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. > >Joel Andersson > >>Input scheme: casadi::SDPInput (SDP_SOLVER_NUM_IN = 9) [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 = 8) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 > >Joel Andersson > >>Input scheme: casadi::SDQPInput (SDQP_SOLVER_NUM_IN = 10) [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 = 8) [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_SDPSOLVER | 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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 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) > >Joris Gillis > >>Input scheme: casadi::SOCPInput (SOCP_SOLVER_NUM_IN = 11) [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 = 5) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 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 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 = 7) [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 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. > >Joel Andersson > >>Input scheme: casadi::StabilizedQPSolverInput (STABILIZED_QP_SOLVER_NUM_IN = 13) [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 = 5) [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 | | >+--------------+--------------+--------------+--------------+--------------+ > >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 SymbolicQR' -- data decl {-| >LinearSolver based on QR factorization with sparsity pattern based >reordering without partial pivoting. > >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. Joel Andersson > >>Input scheme: casadi::LinsolInput (LINSOL_NUM_IN = 3) [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 = 2) [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) | | >+--------------+--------------+--------------+--------------+--------------+ >| codegen | OT_BOOLEAN | false | C-code | casadi::Symb | >| | | | generation | olicQRIntern | >| | | | | al | >+--------------+--------------+--------------+--------------+--------------+ >| compiler | OT_STRING | "gcc -fPIC | Compiler | casadi::Symb | >| | | -O2" | command to | olicQRIntern | >| | | | be used for | al | >| | | | compiling | | >| | | | generated | | >| | | | code | | >+--------------+--------------+--------------+--------------+--------------+ >| 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: symbolic_qr.hpp -} newtype SymbolicQR = SymbolicQR (ForeignPtr SymbolicQR') -- typeclass decl class SymbolicQRClass a where castSymbolicQR :: a -> SymbolicQR instance SymbolicQRClass SymbolicQR where castSymbolicQR = id -- baseclass instances instance FunctionClass SymbolicQR where castFunction (SymbolicQR x) = Function (castForeignPtr x) instance LinearSolverClass SymbolicQR where castLinearSolver (SymbolicQR x) = LinearSolver (castForeignPtr x) instance OptionsFunctionalityClass SymbolicQR where castOptionsFunctionality (SymbolicQR x) = OptionsFunctionality (castForeignPtr x) instance PrintableObjectClass SymbolicQR where castPrintableObject (SymbolicQR x) = PrintableObject (castForeignPtr x) instance SharedObjectClass SymbolicQR where castSharedObject (SymbolicQR x) = SharedObject (castForeignPtr x) instance IOInterfaceFunctionClass SymbolicQR where castIOInterfaceFunction (SymbolicQR x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SymbolicQR (Ptr SymbolicQR') where marshal (SymbolicQR x) = return (unsafeForeignPtrToPtr x) marshalFree (SymbolicQR x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SymbolicQR" c_delete_casadi__SymbolicQR :: FunPtr (Ptr SymbolicQR' -> IO ()) instance WrapReturn (Ptr SymbolicQR') SymbolicQR where wrapReturn = (fmap SymbolicQR) . (newForeignPtr c_delete_casadi__SymbolicQR) -- 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_)