{-# OPTIONS_GHC -Wall #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Wrappers.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.Marshal ( Marshal(..) ) import Casadi.WrapReturn ( WrapReturn(..) ) -- raw decl data SXFunction' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass SXFunction where castSharedObject (SXFunction x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SXFunction where castPrintableObject (SXFunction x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SXFunction where castOptionsFunctionality (SXFunction x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SXFunction where castFunction (SXFunction x) = Function (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 RKIntegrator' -- data decl {-| >[INTERNAL] Fixed-step explicit >Runge-Kutta integrator for ODEs Currently implements RK4. > >The method is still under development > >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 | >| | | | wether | | >| | | | 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_fi | OT_INTEGER | 20 | Number of | CasADi::Fixe | >| nite_element | | | finite | dStepIntegra | >| s | | | elements | torInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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: rk_integrator.hpp -} newtype RKIntegrator = RKIntegrator (ForeignPtr RKIntegrator') -- typeclass decl class RKIntegratorClass a where castRKIntegrator :: a -> RKIntegrator instance RKIntegratorClass RKIntegrator where castRKIntegrator = id -- baseclass instances instance SharedObjectClass RKIntegrator where castSharedObject (RKIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass RKIntegrator where castPrintableObject (RKIntegrator x) = PrintableObject (castForeignPtr x) instance FixedStepIntegratorClass RKIntegrator where castFixedStepIntegrator (RKIntegrator x) = FixedStepIntegrator (castForeignPtr x) instance OptionsFunctionalityClass RKIntegrator where castOptionsFunctionality (RKIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass RKIntegrator where castFunction (RKIntegrator x) = Function (castForeignPtr x) instance IntegratorClass RKIntegrator where castIntegrator (RKIntegrator x) = Integrator (castForeignPtr x) instance IOInterfaceFunctionClass RKIntegrator where castIOInterfaceFunction (RKIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal RKIntegrator (Ptr RKIntegrator') where marshal (RKIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (RKIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__RKIntegrator" c_delete_CasADi__RKIntegrator :: FunPtr (Ptr RKIntegrator' -> IO ()) instance WrapReturn (Ptr RKIntegrator') RKIntegrator where wrapReturn = (fmap RKIntegrator) . (newForeignPtr c_delete_CasADi__RKIntegrator) -- raw decl data SQPMethod' -- data decl {-| >[INTERNAL] Sequential Quadratic >Programming method. > >The algorithm is a classical SQP method with either exact (may be also >provided) or damped BFGS Lagrange Hessian approximation. Two different line- >search algorithms are available. First, Armijo (Wolfe) condition with >backtracking (suffers from Maratos effect). Seco::ifndef >WITHOUT_PRE_1_9_Xnd, a line-search method that checks if the merit function >is lower than the last k values (no Maratos effect). Both methods employ the >L1 merit function. > >The method solves the problems of form:min F(x) x subject to LBG ><= G(x) <= UBG LBX <= x <= UBX > >Nonlinear equalities can be introduced by setting LBG and UBG equal at the >correct positions. > >The method is still under development and should be used with care > >Attila Kozma, Joel Andersson and 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) | | >+--------------+--------------+--------------+--------------+--------------+ >| beta | OT_REAL | 0.800 | Line-search | CasADi::SQPI | >| | | | parameter, | nternal | >| | | | restoration | | >| | | | factor of | | >| | | | stepsize | | >+--------------+--------------+--------------+--------------+--------------+ >| c1 | OT_REAL | 0.000 | Armijo | CasADi::SQPI | >| | | | condition, | nternal | >| | | | coefficient | | >| | | | of decrease | | >| | | | in merit | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_f | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | objective | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_g | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | constraint | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| gauss_newton | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. Use | olverInterna | >| | | | Gauss Newton | l | >| | | | Hessian appr | | >| | | | oximation | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_gra | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| dient | | ) | option. | olverInterna | >| | | | Generate a | l | >| | | | function for | | >| | | | calculating | | >| | | | the gradient | | >| | | | of the | | >| | | | objective. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_hes | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| sian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Hessian of | | >| | | | the | | >| | | | Lagrangian | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_jac | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| obian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Jacobian of | | >| | | | the | | >| | | | constraints | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| hessian_appr | OT_STRING | "exact" | limited- | CasADi::SQPI | >| oximation | | | memory|exact | nternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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. | | >+--------------+--------------+--------------+--------------+--------------+ >| lbfgs_memory | OT_INTEGER | 10 | Size of | CasADi::SQPI | >| | | | L-BFGS | nternal | >| | | | memory. | | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter | OT_INTEGER | 50 | Maximum | CasADi::SQPI | >| | | | number of | nternal | >| | | | SQP | | >| | | | iterations | | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter_ls | OT_INTEGER | 3 | Maximum | CasADi::SQPI | >| | | | number of | nternal | >| | | | linesearch | | >| | | | iterations | | >+--------------+--------------+--------------+--------------+--------------+ >| merit_memory | OT_INTEGER | 4 | Size of | CasADi::SQPI | >| | | | memory to | nternal | >| | | | store | | >| | | | history of | | >| | | | merit | | >| | | | function | | >| | | | values | | >+--------------+--------------+--------------+--------------+--------------+ >| min_step_siz | OT_REAL | 0.000 | The size | CasADi::SQPI | >| e | | | (inf-norm) | nternal | >| | | | of the step | | >| | | | size should | | >| | | | not become | | >| | | | smaller than | | >| | | | this. | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::SQPI | >| | | | uts) (eval_ | nternal | >| | | | f|eval_g|eva | | >| | | | l_jac_g|eval | | >| | | | _grad_f|eval | | >| | | | _h|qp|dx) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | CasADi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| parametric | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. | olverInterna | >| | | | Expect F, G, | l | >| | | | H, J to have | | >| | | | an | | >| | | | additional | | >| | | | input | | >| | | | argument | | >| | | | appended at | | >| | | | the end, | | >| | | | denoting | | >| | | | fixed | | >| | | | parameters. | | >+--------------+--------------+--------------+--------------+--------------+ >| print_header | OT_BOOLEAN | true | Print the | CasADi::SQPI | >| | | | header with | nternal | >| | | | problem | | >| | | | statistics | | >+--------------+--------------+--------------+--------------+--------------+ >| print_time | OT_BOOLEAN | true | Print | CasADi::SQPI | >| | | | information | nternal | >| | | | about | | >| | | | execution | | >| | | | time | | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver | OT_QPSOLVER | GenericType( | The QP | CasADi::SQPI | >| | | ) | solver to be | nternal | >| | | | used by the | | >| | | | SQP method | | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver_op | OT_DICTIONAR | GenericType( | Options to | CasADi::SQPI | >| tions | Y | ) | be passed to | nternal | >| | | | the QP | | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| regularize | OT_BOOLEAN | false | Automatic re | CasADi::SQPI | >| | | | gularization | nternal | >| | | | of Lagrange | | >| | | | Hessian. | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_du | OT_REAL | 0.000 | Stopping | CasADi::SQPI | >| | | | criterion | nternal | >| | | | for dual inf | | >| | | | easability | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_pr | OT_REAL | 0.000 | Stopping | CasADi::SQPI | >| | | | criterion | nternal | >| | | | for primal i | | >| | | | nfeasibility | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | CasADi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | CasADi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ >| warn_initial | OT_BOOLEAN | false | Warn if the | CasADi::NLPS | >| _bounds | | | initial | olverInterna | >| | | | guess does | l | >| | | | not satisfy | | >| | | | LBX and UBX | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available monitors >+-------------+--------------------------+ >| Id | Used in | >+=============+==========================+ >| dx | CasADi::SQPInternal | >+-------------+--------------------------+ >| eval_f | CasADi::SQPInternal | >+-------------+--------------------------+ >| eval_g | CasADi::SQPInternal | >+-------------+--------------------------+ >| eval_grad_f | CasADi::SQPInternal | >+-------------+--------------------------+ >| eval_h | CasADi::SQPInternal | >+-------------+--------------------------+ >| eval_jac_g | CasADi::SQPInternal | >+-------------+--------------------------+ >| inputs | CasADi::FunctionInternal | >+-------------+--------------------------+ >| outputs | CasADi::FunctionInternal | >+-------------+--------------------------+ >| qp | CasADi::SQPInternal | >+-------------+--------------------------+ > >>List of available stats >+--------------------+---------------------+ >| Id | Used in | >+====================+=====================+ >| iter_count | CasADi::SQPInternal | >+--------------------+---------------------+ >| iteration | CasADi::SQPInternal | >+--------------------+---------------------+ >| iterations | CasADi::SQPInternal | >+--------------------+---------------------+ >| n_eval_f | CasADi::SQPInternal | >+--------------------+---------------------+ >| n_eval_g | CasADi::SQPInternal | >+--------------------+---------------------+ >| n_eval_grad_f | CasADi::SQPInternal | >+--------------------+---------------------+ >| n_eval_h | CasADi::SQPInternal | >+--------------------+---------------------+ >| n_eval_jac_g | CasADi::SQPInternal | >+--------------------+---------------------+ >| return_status | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_callback_fun | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_callback_prepare | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_eval_f | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_eval_g | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_eval_grad_f | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_eval_h | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_eval_jac_g | CasADi::SQPInternal | >+--------------------+---------------------+ >| t_mainloop | CasADi::SQPInternal | >+--------------------+---------------------+ > >Diagrams > >C++ includes: sqp_method.hpp -} newtype SQPMethod = SQPMethod (ForeignPtr SQPMethod') -- typeclass decl class SQPMethodClass a where castSQPMethod :: a -> SQPMethod instance SQPMethodClass SQPMethod where castSQPMethod = id -- baseclass instances instance SharedObjectClass SQPMethod where castSharedObject (SQPMethod x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SQPMethod where castPrintableObject (SQPMethod x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SQPMethod where castOptionsFunctionality (SQPMethod x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SQPMethod where castFunction (SQPMethod x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass SQPMethod where castIOInterfaceFunction (SQPMethod x) = IOInterfaceFunction (castForeignPtr x) instance NLPSolverClass SQPMethod where castNLPSolver (SQPMethod x) = NLPSolver (castForeignPtr x) -- helper instances instance Marshal SQPMethod (Ptr SQPMethod') where marshal (SQPMethod x) = return (unsafeForeignPtrToPtr x) marshalFree (SQPMethod x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SQPMethod" c_delete_CasADi__SQPMethod :: FunPtr (Ptr SQPMethod' -> IO ()) instance WrapReturn (Ptr SQPMethod') SQPMethod where wrapReturn = (fmap SQPMethod) . (newForeignPtr c_delete_CasADi__SQPMethod) -- raw decl data SharedObject' -- data decl {-| >[INTERNAL] SharedObject >implements a reference counting framework simular for effient 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 destinction 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 explictly. 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 MXFunction' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass MXFunction where castSharedObject (MXFunction x) = SharedObject (castForeignPtr x) instance PrintableObjectClass MXFunction where castPrintableObject (MXFunction x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass MXFunction where castOptionsFunctionality (MXFunction x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass MXFunction where castFunction (MXFunction x) = Function (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 HomotopyNLPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass HomotopyNLPSolver where castSharedObject (HomotopyNLPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass HomotopyNLPSolver where castPrintableObject (HomotopyNLPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass HomotopyNLPSolver where castOptionsFunctionality (HomotopyNLPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass HomotopyNLPSolver where castFunction (HomotopyNLPSolver x) = Function (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 StabilizedQPSolver' -- data decl {-| >[INTERNAL] >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 | >| | | | wether | | >| | | | 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 SharedObjectClass StabilizedQPSolver where castSharedObject (StabilizedQPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass StabilizedQPSolver where castPrintableObject (StabilizedQPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass StabilizedQPSolver where castOptionsFunctionality (StabilizedQPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass StabilizedQPSolver where castFunction (StabilizedQPSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass StabilizedQPSolver where castIOInterfaceFunction (StabilizedQPSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal StabilizedQPSolver (Ptr StabilizedQPSolver') where marshal (StabilizedQPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (StabilizedQPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__StabilizedQPSolver" c_delete_CasADi__StabilizedQPSolver :: FunPtr (Ptr StabilizedQPSolver' -> IO ()) instance WrapReturn (Ptr StabilizedQPSolver') StabilizedQPSolver where wrapReturn = (fmap StabilizedQPSolver) . (newForeignPtr c_delete_CasADi__StabilizedQPSolver) -- raw decl data SymbolicNLP' -- data decl {-| >[INTERNAL] A symbolic NLP >representation. > >Joel Andersson > >C++ includes: symbolic_nlp.hpp -} newtype SymbolicNLP = SymbolicNLP (ForeignPtr SymbolicNLP') -- typeclass decl class SymbolicNLPClass a where castSymbolicNLP :: a -> SymbolicNLP instance SymbolicNLPClass SymbolicNLP where castSymbolicNLP = id -- baseclass instances instance PrintableObjectClass SymbolicNLP where castPrintableObject (SymbolicNLP x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SymbolicNLP (Ptr SymbolicNLP') where marshal (SymbolicNLP x) = return (unsafeForeignPtrToPtr x) marshalFree (SymbolicNLP x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SymbolicNLP" c_delete_CasADi__SymbolicNLP :: FunPtr (Ptr SymbolicNLP' -> IO ()) instance WrapReturn (Ptr SymbolicNLP') SymbolicNLP where wrapReturn = (fmap SymbolicNLP) . (newForeignPtr c_delete_CasADi__SymbolicNLP) -- raw decl data CSparse' -- data decl {-| >[INTERNAL] LinearSolver with >CSparse Interface. > >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. > >CSparse is an CasADi::Function mapping from 2 inputs [ A (matrix),b >(vector)] to one output [x (vector)]. > >The usual procedure to use CSparse is: init() > >set the first input (A) > >prepare() > >set the second input (b) > >solve() > >Repeat steps 4 and 5 to work with other b vectors. > >The method evaluate() combines the prepare() and solve() step and is >therefore more expensive if A is invariant. > >>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 | >| | | | wether | | >| | | | 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: csparse.hpp -} newtype CSparse = CSparse (ForeignPtr CSparse') -- typeclass decl class CSparseClass a where castCSparse :: a -> CSparse instance CSparseClass CSparse where castCSparse = id -- baseclass instances instance SharedObjectClass CSparse where castSharedObject (CSparse x) = SharedObject (castForeignPtr x) instance PrintableObjectClass CSparse where castPrintableObject (CSparse x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass CSparse where castOptionsFunctionality (CSparse x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass CSparse where castFunction (CSparse x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass CSparse where castIOInterfaceFunction (CSparse x) = IOInterfaceFunction (castForeignPtr x) instance LinearSolverClass CSparse where castLinearSolver (CSparse x) = LinearSolver (castForeignPtr x) -- helper instances instance Marshal CSparse (Ptr CSparse') where marshal (CSparse x) = return (unsafeForeignPtrToPtr x) marshalFree (CSparse x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__CSparse" c_delete_CasADi__CSparse :: FunPtr (Ptr CSparse' -> IO ()) instance WrapReturn (Ptr CSparse') CSparse where wrapReturn = (fmap CSparse) . (newForeignPtr c_delete_CasADi__CSparse) -- raw decl data PrintableObject' -- data decl {-| >[INTERNAL] 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 ExpDMatrix' -- data decl {-| >[INTERNAL] Expression >interface. > >This is a common base class for SX, MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. Joel Andersson > >C++ includes: generic_expression.hpp -} newtype ExpDMatrix = ExpDMatrix (ForeignPtr ExpDMatrix') -- typeclass decl class ExpDMatrixClass a where castExpDMatrix :: a -> ExpDMatrix instance ExpDMatrixClass ExpDMatrix where castExpDMatrix = id -- baseclass instances -- helper instances instance Marshal ExpDMatrix (Ptr ExpDMatrix') where marshal (ExpDMatrix x) = return (unsafeForeignPtrToPtr x) marshalFree (ExpDMatrix x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericExpression_CasADi__Matrix_double__" c_delete_CasADi__GenericExpression_CasADi__Matrix_double__ :: FunPtr (Ptr ExpDMatrix' -> IO ()) instance WrapReturn (Ptr ExpDMatrix') ExpDMatrix where wrapReturn = (fmap ExpDMatrix) . (newForeignPtr c_delete_CasADi__GenericExpression_CasADi__Matrix_double__) -- raw decl data QCQPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass QCQPSolver where castSharedObject (QCQPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass QCQPSolver where castPrintableObject (QCQPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass QCQPSolver where castOptionsFunctionality (QCQPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass QCQPSolver where castFunction (QCQPSolver x) = Function (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 NLPSolver' -- data decl {-| >[INTERNAL] 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_f | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | objective | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_g | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | constraint | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| gauss_newton | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. Use | olverInterna | >| | | | Gauss Newton | l | >| | | | Hessian appr | | >| | | | oximation | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_gra | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| dient | | ) | option. | olverInterna | >| | | | Generate a | l | >| | | | function for | | >| | | | calculating | | >| | | | the gradient | | >| | | | of the | | >| | | | objective. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_hes | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| sian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Hessian of | | >| | | | the | | >| | | | Lagrangian | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_jac | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| obian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Jacobian of | | >| | | | the | | >| | | | constraints | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| 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. | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| parametric | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. | olverInterna | >| | | | Expect F, G, | l | >| | | | H, J to have | | >| | | | an | | >| | | | additional | | >| | | | input | | >| | | | argument | | >| | | | appended at | | >| | | | the end, | | >| | | | denoting | | >| | | | fixed | | >| | | | parameters. | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 SharedObjectClass NLPSolver where castSharedObject (NLPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass NLPSolver where castPrintableObject (NLPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass NLPSolver where castOptionsFunctionality (NLPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass NLPSolver where castFunction (NLPSolver x) = Function (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 GenericType' -- data decl {-| >[INTERNAL] 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 SharedObjectClass GenericType where castSharedObject (GenericType x) = SharedObject (castForeignPtr x) instance PrintableObjectClass GenericType where castPrintableObject (GenericType x) = PrintableObject (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 NLPQPSolver' -- data decl {-| >[INTERNAL] IPOPT QP Solver for >quadratic programming. > >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. > >Joris Gillis > >>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 | >| | | | wether | | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver | OT_NLPSOLVER | GenericType( | The | CasADi::NLPQ | >| | | ) | NLPSOlver | PInternal | >| | | | used to | | >| | | | solve the | | >| | | | QPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::NLPQ | >| ptions | Y | ) | be passed to | PInternal | >| | | | the | | >| | | | NLPSOlver | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+==================+=======================+ >| nlp_solver_stats | CasADi::NLPQPInternal | >+------------------+-----------------------+ > >Diagrams > >C++ includes: nlp_qp_solver.hpp -} newtype NLPQPSolver = NLPQPSolver (ForeignPtr NLPQPSolver') -- typeclass decl class NLPQPSolverClass a where castNLPQPSolver :: a -> NLPQPSolver instance NLPQPSolverClass NLPQPSolver where castNLPQPSolver = id -- baseclass instances instance SharedObjectClass NLPQPSolver where castSharedObject (NLPQPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass NLPQPSolver where castPrintableObject (NLPQPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass NLPQPSolver where castOptionsFunctionality (NLPQPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass NLPQPSolver where castFunction (NLPQPSolver x) = Function (castForeignPtr x) instance QPSolverClass NLPQPSolver where castQPSolver (NLPQPSolver x) = QPSolver (castForeignPtr x) instance IOInterfaceFunctionClass NLPQPSolver where castIOInterfaceFunction (NLPQPSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal NLPQPSolver (Ptr NLPQPSolver') where marshal (NLPQPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (NLPQPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__NLPQPSolver" c_delete_CasADi__NLPQPSolver :: FunPtr (Ptr NLPQPSolver' -> IO ()) instance WrapReturn (Ptr NLPQPSolver') NLPQPSolver where wrapReturn = (fmap NLPQPSolver) . (newForeignPtr c_delete_CasADi__NLPQPSolver) -- raw decl data Variable' -- data decl {-| >[INTERNAL] Holds expressions and >meta-data corresponding to a physical quantity evolving in time. > >Joel Andersson > >C++ includes: variable.hpp -} newtype Variable = Variable (ForeignPtr Variable') -- typeclass decl class VariableClass a where castVariable :: a -> Variable instance VariableClass Variable where castVariable = id -- baseclass instances instance PrintableObjectClass Variable where castPrintableObject (Variable x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal Variable (Ptr Variable') where marshal (Variable x) = return (unsafeForeignPtrToPtr x) marshalFree (Variable x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__Variable" c_delete_CasADi__Variable :: FunPtr (Ptr Variable' -> IO ()) instance WrapReturn (Ptr Variable') Variable where wrapReturn = (fmap Variable) . (newForeignPtr c_delete_CasADi__Variable) -- raw decl data LPStructure' -- data decl {-| >[INTERNAL] Helper >function for 'LPStruct' > >C++ includes: casadi_types.hpp -} newtype LPStructure = LPStructure (ForeignPtr LPStructure') -- typeclass decl class LPStructureClass a where castLPStructure :: a -> LPStructure instance LPStructureClass LPStructure where castLPStructure = id -- baseclass instances instance PrintableObjectClass LPStructure where castPrintableObject (LPStructure x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal LPStructure (Ptr LPStructure') where marshal (LPStructure x) = return (unsafeForeignPtrToPtr x) marshalFree (LPStructure x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__LPStructIOSchemeVector_CasADi__Sparsity_" c_delete_CasADi__LPStructIOSchemeVector_CasADi__Sparsity_ :: FunPtr (Ptr LPStructure' -> IO ()) instance WrapReturn (Ptr LPStructure') LPStructure where wrapReturn = (fmap LPStructure) . (newForeignPtr c_delete_CasADi__LPStructIOSchemeVector_CasADi__Sparsity_) -- raw decl data ImplicitFixedStepIntegrator' -- data decl {-| >[INTERNAL] Base >class for implicit fixed step integrators. > >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 | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_sol | OT_IMPLICITF | GenericType( | An implicit | CasADi::Impl | >| ver | UNCTION | ) | function | icitFixedSte | >| | | | solver | pIntegratorI | >| | | | | nternal | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_sol | OT_DICTIONAR | GenericType( | Options to | CasADi::Impl | >| ver_options | Y | ) | be passed to | icitFixedSte | >| | | | the NLP | pIntegratorI | >| | | | Solver | nternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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_fi | OT_INTEGER | 20 | Number of | CasADi::Fixe | >| nite_element | | | finite | dStepIntegra | >| s | | | elements | torInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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: implicit_fixed_step_integrator.hpp -} newtype ImplicitFixedStepIntegrator = ImplicitFixedStepIntegrator (ForeignPtr ImplicitFixedStepIntegrator') -- typeclass decl class ImplicitFixedStepIntegratorClass a where castImplicitFixedStepIntegrator :: a -> ImplicitFixedStepIntegrator instance ImplicitFixedStepIntegratorClass ImplicitFixedStepIntegrator where castImplicitFixedStepIntegrator = id -- baseclass instances instance SharedObjectClass ImplicitFixedStepIntegrator where castSharedObject (ImplicitFixedStepIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass ImplicitFixedStepIntegrator where castPrintableObject (ImplicitFixedStepIntegrator x) = PrintableObject (castForeignPtr x) instance FixedStepIntegratorClass ImplicitFixedStepIntegrator where castFixedStepIntegrator (ImplicitFixedStepIntegrator x) = FixedStepIntegrator (castForeignPtr x) instance OptionsFunctionalityClass ImplicitFixedStepIntegrator where castOptionsFunctionality (ImplicitFixedStepIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass ImplicitFixedStepIntegrator where castFunction (ImplicitFixedStepIntegrator x) = Function (castForeignPtr x) instance IntegratorClass ImplicitFixedStepIntegrator where castIntegrator (ImplicitFixedStepIntegrator x) = Integrator (castForeignPtr x) instance IOInterfaceFunctionClass ImplicitFixedStepIntegrator where castIOInterfaceFunction (ImplicitFixedStepIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal ImplicitFixedStepIntegrator (Ptr ImplicitFixedStepIntegrator') where marshal (ImplicitFixedStepIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (ImplicitFixedStepIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__ImplicitFixedStepIntegrator" c_delete_CasADi__ImplicitFixedStepIntegrator :: FunPtr (Ptr ImplicitFixedStepIntegrator' -> IO ()) instance WrapReturn (Ptr ImplicitFixedStepIntegrator') ImplicitFixedStepIntegrator where wrapReturn = (fmap ImplicitFixedStepIntegrator) . (newForeignPtr c_delete_CasADi__ImplicitFixedStepIntegrator) -- raw decl data CSparseCholesky' -- data decl {-| >[INTERNAL] LinearSolver >with CSparseCholesky Interface. > >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. > >CSparseCholesky is an CasADi::Function mapping from 2 inputs [ A (matrix),b >(vector)] to one output [x (vector)]. > >A = LL' Ax = b LL'x = b L'x = L^-1 b > >The usual procedure to use CSparseCholesky is: init() > >set the first input (A) > >prepare() > >set the second input (b) > >solve() > >Repeat steps 4 and 5 to work with other b vectors. > >The method evaluate() combines the prepare() and solve() step and is >therefore more expensive if A is invariant. > >>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 | >| | | | wether | | >| | | | 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: csparse_cholesky.hpp -} newtype CSparseCholesky = CSparseCholesky (ForeignPtr CSparseCholesky') -- typeclass decl class CSparseCholeskyClass a where castCSparseCholesky :: a -> CSparseCholesky instance CSparseCholeskyClass CSparseCholesky where castCSparseCholesky = id -- baseclass instances instance SharedObjectClass CSparseCholesky where castSharedObject (CSparseCholesky x) = SharedObject (castForeignPtr x) instance PrintableObjectClass CSparseCholesky where castPrintableObject (CSparseCholesky x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass CSparseCholesky where castOptionsFunctionality (CSparseCholesky x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass CSparseCholesky where castFunction (CSparseCholesky x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass CSparseCholesky where castIOInterfaceFunction (CSparseCholesky x) = IOInterfaceFunction (castForeignPtr x) instance LinearSolverClass CSparseCholesky where castLinearSolver (CSparseCholesky x) = LinearSolver (castForeignPtr x) -- helper instances instance Marshal CSparseCholesky (Ptr CSparseCholesky') where marshal (CSparseCholesky x) = return (unsafeForeignPtrToPtr x) marshalFree (CSparseCholesky x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__CSparseCholesky" c_delete_CasADi__CSparseCholesky :: FunPtr (Ptr CSparseCholesky' -> IO ()) instance WrapReturn (Ptr CSparseCholesky') CSparseCholesky where wrapReturn = (fmap CSparseCholesky) . (newForeignPtr c_delete_CasADi__CSparseCholesky) -- raw decl data SDPSOCPSolver' -- data decl {-| >[INTERNAL] SOCP Solver for >quadratic programming. > >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 | >| | | | wether | | >| | | | 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| sdp_solver | OT_SDPSOLVER | GenericType( | The | CasADi::SDPS | >| | | ) | SDPSolver | OCPInternal | >| | | | used to | | >| | | | solve the | | >| | | | SOCPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| sdp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::SDPS | >| ptions | Y | ) | be passed to | OCPInternal | >| | | | the | | >| | | | SDPSOlver | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | CasADi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | CasADi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available stats >+------------------+-------------------------+ >| Id | Used in | >+==================+=========================+ >| sdp_solver_stats | CasADi::SDPSOCPInternal | >+------------------+-------------------------+ > >Diagrams > >C++ includes: sdp_socp_solver.hpp -} newtype SDPSOCPSolver = SDPSOCPSolver (ForeignPtr SDPSOCPSolver') -- typeclass decl class SDPSOCPSolverClass a where castSDPSOCPSolver :: a -> SDPSOCPSolver instance SDPSOCPSolverClass SDPSOCPSolver where castSDPSOCPSolver = id -- baseclass instances instance SharedObjectClass SDPSOCPSolver where castSharedObject (SDPSOCPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SDPSOCPSolver where castPrintableObject (SDPSOCPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SDPSOCPSolver where castOptionsFunctionality (SDPSOCPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SDPSOCPSolver where castFunction (SDPSOCPSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass SDPSOCPSolver where castIOInterfaceFunction (SDPSOCPSolver x) = IOInterfaceFunction (castForeignPtr x) instance SOCPSolverClass SDPSOCPSolver where castSOCPSolver (SDPSOCPSolver x) = SOCPSolver (castForeignPtr x) -- helper instances instance Marshal SDPSOCPSolver (Ptr SDPSOCPSolver') where marshal (SDPSOCPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SDPSOCPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SDPSOCPSolver" c_delete_CasADi__SDPSOCPSolver :: FunPtr (Ptr SDPSOCPSolver' -> IO ()) instance WrapReturn (Ptr SDPSOCPSolver') SDPSOCPSolver where wrapReturn = (fmap SDPSOCPSolver) . (newForeignPtr c_delete_CasADi__SDPSOCPSolver) -- raw decl data OptionsFunctionality' -- data decl {-| >[INTERNAL] 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 SharedObjectClass OptionsFunctionality where castSharedObject (OptionsFunctionality x) = SharedObject (castForeignPtr x) instance PrintableObjectClass OptionsFunctionality where castPrintableObject (OptionsFunctionality x) = PrintableObject (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 OldCollocationIntegrator' -- data decl {-| >[INTERNAL] >Collocation integrator ODE/DAE integrator based on collocation. > >The method is still under development > >Base class for integrators. 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. > >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. | | >+--------------+--------------+--------------+--------------+--------------+ >| collocation_ | OT_STRING | "radau" | Collocation | CasADi::OldC | >| scheme | | | scheme (rada | ollocationIn | >| | | | u|legendre) | tegratorInte | >| | | | | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_f | OT_BOOLEAN | false | Expand the | CasADi::OldC | >| | | | ODE/DAE | ollocationIn | >| | | | residual | tegratorInte | >| | | | function in | rnal | >| | | | an SX graph | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_q | OT_BOOLEAN | false | Expand the | CasADi::OldC | >| | | | quadrature | ollocationIn | >| | | | function in | tegratorInte | >| | | | an SX graph | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| hotstart | OT_BOOLEAN | true | Initialize | CasADi::OldC | >| | | | the | ollocationIn | >| | | | trajectory | tegratorInte | >| | | | at the | rnal | >| | | | previous | | >| | | | solution | | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_sol | OT_IMPLICITF | GenericType( | An implicit | CasADi::OldC | >| ver | UNCTION | ) | function | ollocationIn | >| | | | solver | tegratorInte | >| | | | | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_sol | OT_DICTIONAR | GenericType( | Options to | CasADi::OldC | >| ver_options | Y | ) | be passed to | ollocationIn | >| | | | the implicit | tegratorInte | >| | | | solver | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | CasADi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| interpolatio | OT_INTEGER | 3 | Order of the | CasADi::OldC | >| n_order | | | interpolatin | ollocationIn | >| | | | g | tegratorInte | >| | | | polynomials | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| 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_fi | OT_INTEGER | 20 | Number of | CasADi::OldC | >| nite_element | | | finite | ollocationIn | >| s | | | elements | tegratorInte | >| | | | | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| print_stats | OT_BOOLEAN | false | Print out | CasADi::Inte | >| | | | statistics | gratorIntern | >| | | | after | al | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| quadrature_s | OT_LINEARSOL | GenericType( | An linear | CasADi::OldC | >| olver | VER | ) | solver to | ollocationIn | >| | | | solver the | tegratorInte | >| | | | quadrature | rnal | >| | | | equations | | >+--------------+--------------+--------------+--------------+--------------+ >| quadrature_s | OT_DICTIONAR | GenericType( | Options to | CasADi::OldC | >| olver_option | Y | ) | be passed to | ollocationIn | >| s | | | the | tegratorInte | >| | | | quadrature | rnal | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| startup_inte | OT_INTEGRATO | GenericType( | An ODE/DAE | CasADi::OldC | >| grator | R | ) | integrator | ollocationIn | >| | | | that can be | tegratorInte | >| | | | used to | rnal | >| | | | generate a | | >| | | | startup | | >| | | | trajectory | | >+--------------+--------------+--------------+--------------+--------------+ >| startup_inte | OT_DICTIONAR | GenericType( | Options to | CasADi::OldC | >| grator_optio | Y | ) | be passed to | ollocationIn | >| ns | | | the startup | tegratorInte | >| | | | integrator | rnal | >+--------------+--------------+--------------+--------------+--------------+ >| 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: old_collocation_integrator.hpp -} newtype OldCollocationIntegrator = OldCollocationIntegrator (ForeignPtr OldCollocationIntegrator') -- typeclass decl class OldCollocationIntegratorClass a where castOldCollocationIntegrator :: a -> OldCollocationIntegrator instance OldCollocationIntegratorClass OldCollocationIntegrator where castOldCollocationIntegrator = id -- baseclass instances instance SharedObjectClass OldCollocationIntegrator where castSharedObject (OldCollocationIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass OldCollocationIntegrator where castPrintableObject (OldCollocationIntegrator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass OldCollocationIntegrator where castOptionsFunctionality (OldCollocationIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass OldCollocationIntegrator where castFunction (OldCollocationIntegrator x) = Function (castForeignPtr x) instance IntegratorClass OldCollocationIntegrator where castIntegrator (OldCollocationIntegrator x) = Integrator (castForeignPtr x) instance IOInterfaceFunctionClass OldCollocationIntegrator where castIOInterfaceFunction (OldCollocationIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal OldCollocationIntegrator (Ptr OldCollocationIntegrator') where marshal (OldCollocationIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (OldCollocationIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__OldCollocationIntegrator" c_delete_CasADi__OldCollocationIntegrator :: FunPtr (Ptr OldCollocationIntegrator' -> IO ()) instance WrapReturn (Ptr OldCollocationIntegrator') OldCollocationIntegrator where wrapReturn = (fmap OldCollocationIntegrator) . (newForeignPtr c_delete_CasADi__OldCollocationIntegrator) -- raw decl data FixedStepIntegrator' -- data decl {-| >[INTERNAL] Base class >for fixed step integrators. > >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 | >| | | | wether | | >| | | | 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_fi | OT_INTEGER | 20 | Number of | CasADi::Fixe | >| nite_element | | | finite | dStepIntegra | >| s | | | elements | torInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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: fixed_step_integrator.hpp -} newtype FixedStepIntegrator = FixedStepIntegrator (ForeignPtr FixedStepIntegrator') -- typeclass decl class FixedStepIntegratorClass a where castFixedStepIntegrator :: a -> FixedStepIntegrator instance FixedStepIntegratorClass FixedStepIntegrator where castFixedStepIntegrator = id -- baseclass instances instance SharedObjectClass FixedStepIntegrator where castSharedObject (FixedStepIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass FixedStepIntegrator where castPrintableObject (FixedStepIntegrator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass FixedStepIntegrator where castOptionsFunctionality (FixedStepIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass FixedStepIntegrator where castFunction (FixedStepIntegrator x) = Function (castForeignPtr x) instance IntegratorClass FixedStepIntegrator where castIntegrator (FixedStepIntegrator x) = Integrator (castForeignPtr x) instance IOInterfaceFunctionClass FixedStepIntegrator where castIOInterfaceFunction (FixedStepIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal FixedStepIntegrator (Ptr FixedStepIntegrator') where marshal (FixedStepIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (FixedStepIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__FixedStepIntegrator" c_delete_CasADi__FixedStepIntegrator :: FunPtr (Ptr FixedStepIntegrator' -> IO ()) instance WrapReturn (Ptr FixedStepIntegrator') FixedStepIntegrator where wrapReturn = (fmap FixedStepIntegrator) . (newForeignPtr c_delete_CasADi__FixedStepIntegrator) -- raw decl data CollocationIntegrator' -- data decl {-| >[INTERNAL] Fixed-step >implicit Runge-Kutta integrator ODE/DAE integrator based on collocation >schemes. > >The method is still under development > >Base class for integrators. 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. > >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. | | >+--------------+--------------+--------------+--------------+--------------+ >| collocation_ | OT_STRING | "radau" | Collocation | CasADi::Coll | >| scheme | | | scheme (rada | ocationInteg | >| | | | u|legendre) | ratorInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_sol | OT_IMPLICITF | GenericType( | An implicit | CasADi::Impl | >| ver | UNCTION | ) | function | icitFixedSte | >| | | | solver | pIntegratorI | >| | | | | nternal | >+--------------+--------------+--------------+--------------+--------------+ >| implicit_sol | OT_DICTIONAR | GenericType( | Options to | CasADi::Impl | >| ver_options | Y | ) | be passed to | icitFixedSte | >| | | | the NLP | pIntegratorI | >| | | | Solver | nternal | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | CasADi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| interpolatio | OT_INTEGER | 3 | Order of the | CasADi::Coll | >| n_order | | | interpolatin | ocationInteg | >| | | | g | ratorInterna | >| | | | polynomials | l | >+--------------+--------------+--------------+--------------+--------------+ >| 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_fi | OT_INTEGER | 20 | Number of | CasADi::Fixe | >| nite_element | | | finite | dStepIntegra | >| s | | | elements | torInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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: collocation_integrator.hpp -} newtype CollocationIntegrator = CollocationIntegrator (ForeignPtr CollocationIntegrator') -- typeclass decl class CollocationIntegratorClass a where castCollocationIntegrator :: a -> CollocationIntegrator instance CollocationIntegratorClass CollocationIntegrator where castCollocationIntegrator = id -- baseclass instances instance SharedObjectClass CollocationIntegrator where castSharedObject (CollocationIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass CollocationIntegrator where castPrintableObject (CollocationIntegrator x) = PrintableObject (castForeignPtr x) instance ImplicitFixedStepIntegratorClass CollocationIntegrator where castImplicitFixedStepIntegrator (CollocationIntegrator x) = ImplicitFixedStepIntegrator (castForeignPtr x) instance FixedStepIntegratorClass CollocationIntegrator where castFixedStepIntegrator (CollocationIntegrator x) = FixedStepIntegrator (castForeignPtr x) instance OptionsFunctionalityClass CollocationIntegrator where castOptionsFunctionality (CollocationIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass CollocationIntegrator where castFunction (CollocationIntegrator x) = Function (castForeignPtr x) instance IntegratorClass CollocationIntegrator where castIntegrator (CollocationIntegrator x) = Integrator (castForeignPtr x) instance IOInterfaceFunctionClass CollocationIntegrator where castIOInterfaceFunction (CollocationIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal CollocationIntegrator (Ptr CollocationIntegrator') where marshal (CollocationIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (CollocationIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__CollocationIntegrator" c_delete_CasADi__CollocationIntegrator :: FunPtr (Ptr CollocationIntegrator' -> IO ()) instance WrapReturn (Ptr CollocationIntegrator') CollocationIntegrator where wrapReturn = (fmap CollocationIntegrator) . (newForeignPtr c_delete_CasADi__CollocationIntegrator) -- raw decl data GenSX' -- data decl {-| >[INTERNAL] Matrix base >class. > >This is a common base class for MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. The class is designed with the idea that >"everything is a matrix", that is, also scalars and vectors. This >philosophy makes it easy to use and to interface in particularily with >Python and Matlab/Octave. The syntax tries to stay as close as possible to >the ublas syntax when it comes to vector/matrix operations. Index starts >with 0. Index vec happens as follows: (rr,cc) -> k = rr+cc*size1() Vectors >are column vectors. The storage format is Compressed Column Storage (CCS), >similar to that used for sparse matrices in Matlab, but unlike this format, >we do allow for elements to be structurally non-zero but numerically zero. >The sparsity pattern, which is reference counted and cached, can be accessed >with Sparsity& sparsity() Joel Andersson > >C++ includes: generic_matrix.hpp -} newtype GenSX = GenSX (ForeignPtr GenSX') -- typeclass decl class GenSXClass a where castGenSX :: a -> GenSX instance GenSXClass GenSX where castGenSX = id -- baseclass instances -- helper instances instance Marshal GenSX (Ptr GenSX') where marshal (GenSX x) = return (unsafeForeignPtrToPtr x) marshalFree (GenSX x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericMatrix_CasADi__Matrix_CasADi__SXElement__" c_delete_CasADi__GenericMatrix_CasADi__Matrix_CasADi__SXElement__ :: FunPtr (Ptr GenSX' -> IO ()) instance WrapReturn (Ptr GenSX') GenSX where wrapReturn = (fmap GenSX) . (newForeignPtr c_delete_CasADi__GenericMatrix_CasADi__Matrix_CasADi__SXElement__) -- raw decl data IpoptSolver' -- data decl {-| >[INTERNAL] interface to IPOPT >NLP solver > >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 > >When in warmstart mode, output NLP_SOLVER_LAM_X may be used as input > >NOTE: Even when max_iter == 0, it is not guaranteed that >input(NLP_SOLVER_X0) == output(NLP_SOLVER_X). Indeed if bounds on X or >constraints are unmet, they will differ. > >For a good tutorial on IPOPT, >seehttp://drops.dagstuhl.de/volltexte/2009/2089/pdf/09061.WaechterAndreas.Paper.2089.pdf > >A good resource about the algorithms in IPOPT is: Wachter and L. T. Biegler, >On the Implementation of an Interior-Point Filter Line-Search Algorithm for >Large-Scale Nonlinear Programming, Mathematical Programming 106(1), pp. >25-57, 2006 (As Research Report RC 23149, IBM T. J. Watson Research Center, >Yorktown, USA > >Caveats: with default options, multipliers for the decision variables are >wrong for equality constraints. Change the 'fixed_variable_treatment' to >'make_constraint' or 'relax_bounds' to obtain correct results. > >>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 | >+==============+==============+==============+==============+==============+ >| accept_after | OT_INTEGER | -1 | Accept a | CasADi::Ipop | >| _max_steps | | | trial point | tInternal | >| | | | after | | >| | | | maximal this | | >| | | | number of | | >| | | | steps. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| accept_every | OT_STRING | no | Always | CasADi::Ipop | >| _trial_step | | | accept the | tInternal | >| | | | first trial | | >| | | | step. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| acceptable_c | OT_REAL | 0.010 | "Acceptance" | CasADi::Ipop | >| ompl_inf_tol | | | threshold | tInternal | >| | | | for the comp | | >| | | | lementarity | | >| | | | conditions. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| acceptable_c | OT_REAL | 0.010 | "Acceptance" | CasADi::Ipop | >| onstr_viol_t | | | threshold | tInternal | >| ol | | | for the | | >| | | | constraint | | >| | | | violation. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| acceptable_d | OT_REAL | 1.000e+10 | "Acceptance" | CasADi::Ipop | >| ual_inf_tol | | | threshold | tInternal | >| | | | for the dual | | >| | | | infeasibilit | | >| | | | y. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| acceptable_i | OT_INTEGER | 15 | Number of | CasADi::Ipop | >| ter | | | "acceptable" | tInternal | >| | | | iterates | | >| | | | before | | >| | | | triggering | | >| | | | termination. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| acceptable_o | OT_REAL | 1.000e+20 | "Acceptance" | CasADi::Ipop | >| bj_change_to | | | stopping | tInternal | >| l | | | criterion | | >| | | | based on | | >| | | | objective | | >| | | | function | | >| | | | change. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| acceptable_t | OT_REAL | 0.000 | "Acceptable" | CasADi::Ipop | >| ol | | | convergence | tInternal | >| | | | tolerance | | >| | | | (relative). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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) | | >+--------------+--------------+--------------+--------------+--------------+ >| adaptive_mu_ | OT_STRING | obj-constr- | Globalizatio | CasADi::Ipop | >| globalizatio | | filter | n strategy | tInternal | >| n | | | for the | | >| | | | adaptive mu | | >| | | | selection | | >| | | | mode. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| adaptive_mu_ | OT_STRING | 2-norm- | Norm used | CasADi::Ipop | >| kkt_norm_typ | | squared | for the KKT | tInternal | >| e | | | error in the | | >| | | | adaptive mu | | >| | | | globalizatio | | >| | | | n | | >| | | | strategies. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| adaptive_mu_ | OT_REAL | 1.000 | Sufficient | CasADi::Ipop | >| kkterror_red | | | decrease | tInternal | >| _fact | | | factor for | | >| | | | "kkt-error" | | >| | | | globalizatio | | >| | | | n strategy. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| adaptive_mu_ | OT_INTEGER | 4 | Maximum | CasADi::Ipop | >| kkterror_red | | | number of | tInternal | >| _iters | | | iterations | | >| | | | requiring | | >| | | | sufficient | | >| | | | progress. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| adaptive_mu_ | OT_REAL | 0.800 | Determines | CasADi::Ipop | >| monotone_ini | | | the initial | tInternal | >| t_factor | | | value of the | | >| | | | barrier | | >| | | | parameter | | >| | | | when | | >| | | | switching to | | >| | | | the monotone | | >| | | | mode. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| adaptive_mu_ | OT_STRING | no | Indicates if | CasADi::Ipop | >| restore_prev | | | the previous | tInternal | >| ious_iterate | | | iterate | | >| | | | should be | | >| | | | restored if | | >| | | | the monotone | | >| | | | mode is | | >| | | | entered. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| adaptive_mu_ | OT_REAL | 0 | (see IPOPT d | CasADi::Ipop | >| safeguard_fa | | | ocumentation | tInternal | >| ctor | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| alpha_for_y | OT_STRING | primal | Method to | CasADi::Ipop | >| | | | determine | tInternal | >| | | | the step | | >| | | | size for | | >| | | | constraint | | >| | | | multipliers. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| alpha_for_y_ | OT_REAL | 10 | Tolerance | CasADi::Ipop | >| tol | | | for | tInternal | >| | | | switching to | | >| | | | full | | >| | | | equality | | >| | | | multiplier | | >| | | | steps. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| alpha_min_fr | OT_REAL | 0.050 | Safety | CasADi::Ipop | >| ac | | | factor for | tInternal | >| | | | the minimal | | >| | | | step size | | >| | | | (before | | >| | | | switching to | | >| | | | restoration | | >| | | | phase). (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| alpha_red_fa | OT_REAL | 0.500 | Fractional | CasADi::Ipop | >| ctor | | | reduction of | tInternal | >| | | | the trial | | >| | | | step size in | | >| | | | the | | >| | | | backtracking | | >| | | | line search. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| barrier_tol_ | OT_REAL | 10 | Factor for | CasADi::Ipop | >| factor | | | mu in | tInternal | >| | | | barrier stop | | >| | | | test. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| bound_frac | OT_REAL | 0.010 | Desired | CasADi::Ipop | >| | | | minimum | tInternal | >| | | | relative | | >| | | | distance | | >| | | | from the | | >| | | | initial | | >| | | | point to | | >| | | | bound. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| bound_mult_i | OT_STRING | constant | Initializati | CasADi::Ipop | >| nit_method | | | on method | tInternal | >| | | | for bound | | >| | | | multipliers | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| bound_mult_i | OT_REAL | 1 | Initial | CasADi::Ipop | >| nit_val | | | value for | tInternal | >| | | | the bound | | >| | | | multipliers. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| bound_mult_r | OT_REAL | 1000 | Threshold | CasADi::Ipop | >| eset_thresho | | | for | tInternal | >| ld | | | resetting | | >| | | | bound | | >| | | | multipliers | | >| | | | after the | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| bound_push | OT_REAL | 0.010 | Desired | CasADi::Ipop | >| | | | minimum | tInternal | >| | | | absolute | | >| | | | distance | | >| | | | from the | | >| | | | initial | | >| | | | point to | | >| | | | bound. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| bound_relax_ | OT_REAL | 0.000 | Factor for | CasADi::Ipop | >| factor | | | initial | tInternal | >| | | | relaxation | | >| | | | of the | | >| | | | bounds. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| check_deriva | OT_STRING | no | Indicates | CasADi::Ipop | >| tives_for_na | | | whether it | tInternal | >| ninf | | | is desired | | >| | | | to check for | | >| | | | Nan/Inf in | | >| | | | derivative | | >| | | | matrices | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| chi_cup | OT_REAL | 1.500 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| chi_hat | OT_REAL | 2 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| chi_tilde | OT_REAL | 5 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| compl_inf_to | OT_REAL | 0.000 | Desired | CasADi::Ipop | >| l | | | threshold | tInternal | >| | | | for the comp | | >| | | | lementarity | | >| | | | conditions. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| con_integer_ | OT_DICTIONAR | None | Integer | CasADi::Ipop | >| md | Y | | metadata (a | tInternal | >| | | | dictionary | | >| | | | with lists | | >| | | | of integers) | | >| | | | about | | >| | | | constraints | | >| | | | to be passed | | >| | | | to IPOPT | | >+--------------+--------------+--------------+--------------+--------------+ >| con_numeric_ | OT_DICTIONAR | None | Numeric | CasADi::Ipop | >| md | Y | | metadata (a | tInternal | >| | | | dictionary | | >| | | | with lists | | >| | | | of reals) | | >| | | | about | | >| | | | constraints | | >| | | | to be passed | | >| | | | to IPOPT | | >+--------------+--------------+--------------+--------------+--------------+ >| con_string_m | OT_DICTIONAR | None | String | CasADi::Ipop | >| d | Y | | metadata (a | tInternal | >| | | | dictionary | | >| | | | with lists | | >| | | | of strings) | | >| | | | about | | >| | | | constraints | | >| | | | to be passed | | >| | | | to IPOPT | | >+--------------+--------------+--------------+--------------+--------------+ >| constr_mult_ | OT_REAL | 1000 | Maximum | CasADi::Ipop | >| init_max | | | allowed | tInternal | >| | | | least-square | | >| | | | guess of | | >| | | | constraint | | >| | | | multipliers. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| constr_mult_ | OT_REAL | 0 | Threshold | CasADi::Ipop | >| reset_thresh | | | for | tInternal | >| old | | | resetting | | >| | | | equality and | | >| | | | inequality | | >| | | | multipliers | | >| | | | after | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| constr_viol_ | OT_REAL | 0.000 | Desired | CasADi::Ipop | >| tol | | | threshold | tInternal | >| | | | for the | | >| | | | constraint | | >| | | | violation. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| constraint_v | OT_STRING | 1-norm | Norm to be | CasADi::Ipop | >| iolation_nor | | | used for the | tInternal | >| m_type | | | constraint | | >| | | | violation in | | >| | | | the line | | >| | | | search. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| corrector_co | OT_REAL | 1 | Complementar | CasADi::Ipop | >| mpl_avrg_red | | | ity | tInternal | >| _fact | | | tolerance | | >| | | | factor for | | >| | | | accepting | | >| | | | corrector | | >| | | | step (unsupp | | >| | | | orted!). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| corrector_ty | OT_STRING | none | The type of | CasADi::Ipop | >| pe | | | corrector | tInternal | >| | | | steps that | | >| | | | should be | | >| | | | taken (unsup | | >| | | | ported!). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| delta | OT_REAL | 1 | Multiplier | CasADi::Ipop | >| | | | for | tInternal | >| | | | constraint | | >| | | | violation in | | >| | | | the | | >| | | | switching | | >| | | | rule. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| delta_y_max | OT_REAL | 1.000e+12 | a parameter | CasADi::Ipop | >| | | | used to | tInternal | >| | | | check if the | | >| | | | fast | | >| | | | direction | | >| | | | can be used | | >| | | | asthe line | | >| | | | search | | >| | | | direction | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| dependency_d | OT_STRING | no | Indicates if | CasADi::Ipop | >| etection_wit | | | the right | tInternal | >| h_rhs | | | hand sides | | >| | | | of the | | >| | | | constraints | | >| | | | should be | | >| | | | considered | | >| | | | during | | >| | | | dependency | | >| | | | detection | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| dependency_d | OT_STRING | none | Indicates | CasADi::Ipop | >| etector | | | which linear | tInternal | >| | | | solver | | >| | | | should be | | >| | | | used to | | >| | | | detect | | >| | | | linearly | | >| | | | dependent | | >| | | | equality | | >| | | | constraints. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_t | OT_STRING | none | Enable | CasADi::Ipop | >| est | | | derivative | tInternal | >| | | | checker (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_t | OT_INTEGER | -2 | Index of | CasADi::Ipop | >| est_first_in | | | first | tInternal | >| dex | | | quantity to | | >| | | | be checked | | >| | | | by | | >| | | | derivative | | >| | | | checker (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_t | OT_REAL | 0.000 | Size of the | CasADi::Ipop | >| est_perturba | | | finite | tInternal | >| tion | | | difference | | >| | | | perturbation | | >| | | | in | | >| | | | derivative | | >| | | | test. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_t | OT_STRING | no | Indicates | CasADi::Ipop | >| est_print_al | | | whether | tInternal | >| l | | | information | | >| | | | for all | | >| | | | estimated | | >| | | | derivatives | | >| | | | should be | | >| | | | printed. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| derivative_t | OT_REAL | 0.000 | Threshold | CasADi::Ipop | >| est_tol | | | for | tInternal | >| | | | indicating | | >| | | | wrong | | >| | | | derivative. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| diverging_it | OT_REAL | 1.000e+20 | Threshold | CasADi::Ipop | >| erates_tol | | | for maximal | tInternal | >| | | | value of | | >| | | | primal | | >| | | | iterates. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| dual_inf_tol | OT_REAL | 1 | Desired | CasADi::Ipop | >| | | | threshold | tInternal | >| | | | for the dual | | >| | | | infeasibilit | | >| | | | y. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| epsilon_c | OT_REAL | 0.010 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| eta_min | OT_REAL | 10 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| eta_penalty | OT_REAL | 0.000 | Relaxation | CasADi::Ipop | >| | | | factor in | tInternal | >| | | | the Armijo | | >| | | | condition | | >| | | | for the | | >| | | | penalty | | >| | | | function. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| eta_phi | OT_REAL | 0.000 | Relaxation | CasADi::Ipop | >| | | | factor in | tInternal | >| | | | the Armijo | | >| | | | condition. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| evaluate_ori | OT_STRING | yes | Determines | CasADi::Ipop | >| g_obj_at_res | | | if the | tInternal | >| to_trial | | | original | | >| | | | objective | | >| | | | function | | >| | | | should be | | >| | | | evaluated at | | >| | | | restoration | | >| | | | phase trial | | >| | | | points. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| expand | OT_BOOLEAN | false | Expand the | CasADi::NLPS | >| | | | NLP function | olverInterna | >| | | | in terms of | l | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_f | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | objective | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_g | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | constraint | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| expect_infea | OT_STRING | no | Enable | CasADi::Ipop | >| sible_proble | | | heuristics | tInternal | >| m | | | to quickly | | >| | | | detect an | | >| | | | infeasible | | >| | | | problem. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| expect_infea | OT_REAL | 0.001 | Threshold | CasADi::Ipop | >| sible_proble | | | for | tInternal | >| m_ctol | | | disabling "e | | >| | | | xpect_infeas | | >| | | | ible_problem | | >| | | | " option. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| expect_infea | OT_REAL | 100000000 | Multiplier | CasADi::Ipop | >| sible_proble | | | threshold | tInternal | >| m_ytol | | | for | | >| | | | activating " | | >| | | | expect_infea | | >| | | | sible_proble | | >| | | | m" option. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| fast_des_fac | OT_REAL | 0.100 | a parameter | CasADi::Ipop | >| t | | | used to | tInternal | >| | | | check if the | | >| | | | fast | | >| | | | direction | | >| | | | can be used | | >| | | | asthe line | | >| | | | search | | >| | | | direction | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| fast_step_co | OT_STRING | no | Indicates if | CasADi::Ipop | >| mputation | | | the linear | tInternal | >| | | | system | | >| | | | should be | | >| | | | solved | | >| | | | quickly. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| file_print_l | OT_INTEGER | 5 | Verbosity | CasADi::Ipop | >| evel | | | level for | tInternal | >| | | | output file. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| filter_margi | OT_REAL | 0.000 | Factor | CasADi::Ipop | >| n_fact | | | determining | tInternal | >| | | | width of | | >| | | | margin for | | >| | | | obj-constr- | | >| | | | filter | | >| | | | adaptive glo | | >| | | | balization | | >| | | | strategy. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| filter_max_m | OT_REAL | 1 | Maximum | CasADi::Ipop | >| argin | | | width of | tInternal | >| | | | margin in | | >| | | | obj-constr- | | >| | | | filter | | >| | | | adaptive glo | | >| | | | balization | | >| | | | strategy. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| filter_reset | OT_INTEGER | 5 | Number of | CasADi::Ipop | >| _trigger | | | iterations | tInternal | >| | | | that trigger | | >| | | | the filter | | >| | | | reset. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| findiff_pert | OT_REAL | 0.000 | Size of the | CasADi::Ipop | >| urbation | | | finite | tInternal | >| | | | difference | | >| | | | perturbation | | >| | | | for | | >| | | | derivative a | | >| | | | pproximation | | >| | | | . (see IPOPT | | >| | | | documentatio | | >| | | | n) | | >+--------------+--------------+--------------+--------------+--------------+ >| first_hessia | OT_REAL | 0.000 | Size of | CasADi::Ipop | >| n_perturbati | | | first x-s | tInternal | >| on | | | perturbation | | >| | | | tried. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| fixed_mu_ora | OT_STRING | average_comp | Oracle for | CasADi::Ipop | >| cle | | l | the barrier | tInternal | >| | | | parameter | | >| | | | when | | >| | | | switching to | | >| | | | fixed mode. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| fixed_variab | OT_STRING | make_paramet | Determines | CasADi::Ipop | >| le_treatment | | er | how fixed | tInternal | >| | | | variables | | >| | | | should be | | >| | | | handled. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| gamma_hat | OT_REAL | 0.040 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| gamma_phi | OT_REAL | 0.000 | Relaxation | CasADi::Ipop | >| | | | factor in | tInternal | >| | | | the filter | | >| | | | margin for | | >| | | | the barrier | | >| | | | function. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| gamma_theta | OT_REAL | 0.000 | Relaxation | CasADi::Ipop | >| | | | factor in | tInternal | >| | | | the filter | | >| | | | margin for | | >| | | | the | | >| | | | constraint | | >| | | | violation. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| gamma_tilde | OT_REAL | 4 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| gauss_newton | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. Use | olverInterna | >| | | | Gauss Newton | l | >| | | | Hessian appr | | >| | | | oximation | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_gra | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| dient | | ) | option. | olverInterna | >| | | | Generate a | l | >| | | | function for | | >| | | | calculating | | >| | | | the gradient | | >| | | | of the | | >| | | | objective. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_hes | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| sian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Hessian of | | >| | | | the | | >| | | | Lagrangian | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_jac | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| obian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Jacobian of | | >| | | | the | | >| | | | constraints | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| grad_f | OT_Function | None | Function for | CasADi::Ipop | >| | | | calculating | tInternal | >| | | | the gradient | | >| | | | of the | | >| | | | objective | | >| | | | (column, aut | | >| | | | ogenerated | | >| | | | by default) | | >+--------------+--------------+--------------+--------------+--------------+ >| grad_lag | OT_Function | None | Function for | CasADi::Ipop | >| | | | calculating | tInternal | >| | | | the gradient | | >| | | | of the | | >| | | | Lagrangian ( | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| hess_lag | OT_Function | None | Function for | CasADi::Ipop | >| | | | calculating | tInternal | >| | | | the Hessian | | >| | | | of the | | >| | | | Lagrangian ( | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| hessian_appr | OT_STRING | exact | Indicates | CasADi::Ipop | >| oximation | | | what Hessian | tInternal | >| | | | information | | >| | | | is to be | | >| | | | used. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| hessian_appr | OT_STRING | nonlinear- | Indicates in | CasADi::Ipop | >| oximation_sp | | variables | which | tInternal | >| ace | | | subspace the | | >| | | | Hessian | | >| | | | information | | >| | | | is to be app | | >| | | | roximated. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| hessian_cons | OT_STRING | no | Indicates | CasADi::Ipop | >| tant | | | whether the | tInternal | >| | | | problem is a | | >| | | | quadratic | | >| | | | problem (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| honor_origin | OT_STRING | yes | Indicates | CasADi::Ipop | >| al_bounds | | | whether | tInternal | >| | | | final points | | >| | | | should be | | >| | | | projected | | >| | | | into | | >| | | | original | | >| | | | bounds. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ignore_check | OT_BOOLEAN | false | If set to | CasADi::NLPS | >| _vec | | | true, the | olverInterna | >| | | | input shape | l | >| | | | of F will | | >| | | | not be | | >| | | | checked. | | >+--------------+--------------+--------------+--------------+--------------+ >| inf_pr_outpu | OT_STRING | original | Determines | CasADi::Ipop | >| t | | | what value | tInternal | >| | | | is printed | | >| | | | in the | | >| | | | "inf_pr" | | >| | | | output | | >| | | | column. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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_c_consta | OT_STRING | no | Indicates | CasADi::Ipop | >| nt | | | whether all | tInternal | >| | | | equality | | >| | | | constraints | | >| | | | are linear | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| jac_d_consta | OT_STRING | no | Indicates | CasADi::Ipop | >| nt | | | whether all | tInternal | >| | | | inequality | | >| | | | constraints | | >| | | | are linear | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| jac_f | OT_Function | None | Function for | CasADi::Ipop | >| | | | calculating | tInternal | >| | | | the jacobian | | >| | | | of the | | >| | | | objective | | >| | | | (sparse row, | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| jac_g | OT_Function | None | Function for | CasADi::Ipop | >| | | | calculating | tInternal | >| | | | the Jacobian | | >| | | | of the | | >| | | | constraints | | >| | | | (autogenerat | | >| | | | ed by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| jacobian_app | OT_STRING | exact | Specifies | CasADi::Ipop | >| roximation | | | technique to | tInternal | >| | | | compute | | >| | | | constraint | | >| | | | Jacobian | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| jacobian_reg | OT_REAL | 0.250 | Exponent for | CasADi::Ipop | >| ularization_ | | | mu in the re | tInternal | >| exponent | | | gularization | | >| | | | for rank- | | >| | | | deficient | | >| | | | constraint | | >| | | | Jacobians. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| jacobian_reg | OT_REAL | 0.000 | Size of the | CasADi::Ipop | >| ularization_ | | | regularizati | tInternal | >| value | | | on for rank- | | >| | | | deficient | | >| | | | constraint | | >| | | | Jacobians. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| kappa_d | OT_REAL | 0.000 | Weight for | CasADi::Ipop | >| | | | linear | tInternal | >| | | | damping term | | >| | | | (to handle | | >| | | | one-sided | | >| | | | bounds). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| kappa_sigma | OT_REAL | 1.000e+10 | Factor | CasADi::Ipop | >| | | | limiting the | tInternal | >| | | | deviation of | | >| | | | dual | | >| | | | variables | | >| | | | from primal | | >| | | | estimates. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| kappa_soc | OT_REAL | 0.990 | Factor in | CasADi::Ipop | >| | | | the | tInternal | >| | | | sufficient | | >| | | | reduction | | >| | | | rule for | | >| | | | second order | | >| | | | correction. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| kappa_x_dis | OT_REAL | 100 | a parameter | CasADi::Ipop | >| | | | used to | tInternal | >| | | | check if the | | >| | | | fast | | >| | | | direction | | >| | | | can be used | | >| | | | asthe line | | >| | | | search | | >| | | | direction | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| kappa_y_dis | OT_REAL | 10000 | a parameter | CasADi::Ipop | >| | | | used to | tInternal | >| | | | check if the | | >| | | | fast | | >| | | | direction | | >| | | | can be used | | >| | | | asthe line | | >| | | | search | | >| | | | direction | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| least_square | OT_STRING | no | Least square | CasADi::Ipop | >| _init_duals | | | initializati | tInternal | >| | | | on of all | | >| | | | dual | | >| | | | variables | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| least_square | OT_STRING | no | Least square | CasADi::Ipop | >| _init_primal | | | initializati | tInternal | >| | | | on of the | | >| | | | primal | | >| | | | variables | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_STRING | sherman- | Strategy for | CasADi::Ipop | >| ry_aug_solve | | morrison | solving the | tInternal | >| r | | | augmented | | >| | | | system for | | >| | | | low-rank | | >| | | | Hessian. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_REAL | 1 | Value for B0 | CasADi::Ipop | >| ry_init_val | | | in low-rank | tInternal | >| | | | update. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_REAL | 100000000 | Upper bound | CasADi::Ipop | >| ry_init_val_ | | | on value for | tInternal | >| max | | | B0 in low- | | >| | | | rank update. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_REAL | 0.000 | Lower bound | CasADi::Ipop | >| ry_init_val_ | | | on value for | tInternal | >| min | | | B0 in low- | | >| | | | rank update. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_STRING | scalar1 | Initializati | CasADi::Ipop | >| ry_initializ | | | on strategy | tInternal | >| ation | | | for the | | >| | | | limited | | >| | | | memory | | >| | | | quasi-Newton | | >| | | | approximatio | | >| | | | n. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_INTEGER | 6 | Maximum size | CasADi::Ipop | >| ry_max_histo | | | of the | tInternal | >| ry | | | history for | | >| | | | the limited | | >| | | | quasi-Newton | | >| | | | Hessian appr | | >| | | | oximation. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_INTEGER | 2 | Threshold | CasADi::Ipop | >| ry_max_skipp | | | for | tInternal | >| ing | | | successive | | >| | | | iterations | | >| | | | where update | | >| | | | is skipped. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_STRING | no | Determines | CasADi::Ipop | >| ry_special_f | | | if the | tInternal | >| or_resto | | | quasi-Newton | | >| | | | updates | | >| | | | should be | | >| | | | special | | >| | | | during the | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| limited_memo | OT_STRING | bfgs | Quasi-Newton | CasADi::Ipop | >| ry_update_ty | | | update | tInternal | >| pe | | | formula for | | >| | | | the limited | | >| | | | memory appro | | >| | | | ximation. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| line_search_ | OT_STRING | filter | Globalizatio | CasADi::Ipop | >| method | | | n method | tInternal | >| | | | used in | | >| | | | backtracking | | >| | | | line search | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_scali | OT_STRING | yes | Flag | CasADi::Ipop | >| ng_on_demand | | | indicating | tInternal | >| | | | that linear | | >| | | | scaling is | | >| | | | only done if | | >| | | | it seems | | >| | | | required. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | ma27 | Linear | CasADi::Ipop | >| r | | | solver used | tInternal | >| | | | for step com | | >| | | | putations. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_syste | OT_STRING | mc19 | Method for | CasADi::Ipop | >| m_scaling | | | scaling the | tInternal | >| | | | linear | | >| | | | system. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma27_ignore_ | OT_STRING | no | Enables | CasADi::Ipop | >| singularity | | | MA27's | tInternal | >| | | | ability to | | >| | | | solve a | | >| | | | linear | | >| | | | system even | | >| | | | if the | | >| | | | matrix is | | >| | | | singular. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma27_la_init | OT_REAL | 5 | Real | CasADi::Ipop | >| _factor | | | workspace | tInternal | >| | | | memory for | | >| | | | MA27. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma27_liw_ini | OT_REAL | 5 | Integer | CasADi::Ipop | >| t_factor | | | workspace | tInternal | >| | | | memory for | | >| | | | MA27. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma27_meminc_ | OT_REAL | 10 | Increment | CasADi::Ipop | >| factor | | | factor for | tInternal | >| | | | workspace | | >| | | | size for | | >| | | | MA27. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma27_pivtol | OT_REAL | 0.000 | Pivot | CasADi::Ipop | >| | | | tolerance | tInternal | >| | | | for the | | >| | | | linear | | >| | | | solver MA27. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma27_pivtolm | OT_REAL | 0.000 | Maximum | CasADi::Ipop | >| ax | | | pivot | tInternal | >| | | | tolerance | | >| | | | for the | | >| | | | linear | | >| | | | solver MA27. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma27_skip_in | OT_STRING | no | Always | CasADi::Ipop | >| ertia_check | | | pretend | tInternal | >| | | | inertia is | | >| | | | correct. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma28_pivtol | OT_REAL | 0.010 | Pivot | CasADi::Ipop | >| | | | tolerance | tInternal | >| | | | for linear | | >| | | | solver MA28. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_automat | OT_STRING | yes | Controls | CasADi::Ipop | >| ic_scaling | | | MA57 | tInternal | >| | | | automatic | | >| | | | scaling (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_block_s | OT_INTEGER | 16 | Controls | CasADi::Ipop | >| ize | | | block size | tInternal | >| | | | used by | | >| | | | Level 3 BLAS | | >| | | | in MA57BD | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_node_am | OT_INTEGER | 16 | Node | CasADi::Ipop | >| algamation | | | amalgamation | tInternal | >| | | | parameter | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_pivot_o | OT_INTEGER | 5 | Controls | CasADi::Ipop | >| rder | | | pivot order | tInternal | >| | | | in MA57 (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_pivtol | OT_REAL | 0.000 | Pivot | CasADi::Ipop | >| | | | tolerance | tInternal | >| | | | for the | | >| | | | linear | | >| | | | solver MA57. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_pivtolm | OT_REAL | 0.000 | Maximum | CasADi::Ipop | >| ax | | | pivot | tInternal | >| | | | tolerance | | >| | | | for the | | >| | | | linear | | >| | | | solver MA57. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_pre_all | OT_REAL | 1.050 | Safety | CasADi::Ipop | >| oc | | | factor for | tInternal | >| | | | work space | | >| | | | memory | | >| | | | allocation | | >| | | | for the | | >| | | | linear | | >| | | | solver MA57. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma57_small_p | OT_INTEGER | 0 | If set to 1, | CasADi::Ipop | >| ivot_flag | | | then when | tInternal | >| | | | small | | >| | | | entries | | >| | | | defined by | | >| | | | CNTL(2) are | | >| | | | detected | | >| | | | they are | | >| | | | removed and | | >| | | | the correspo | | >| | | | nding pivots | | >| | | | placed at | | >| | | | the end of | | >| | | | the factoriz | | >| | | | ation. This | | >| | | | can be | | >| | | | particularly | | >| | | | efficient if | | >| | | | the matrix | | >| | | | is highly | | >| | | | rank | | >| | | | deficient. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_nemin | OT_INTEGER | 32 | Node | CasADi::Ipop | >| | | | Amalgamation | tInternal | >| | | | parameter | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_print_l | OT_INTEGER | 0 | Debug | CasADi::Ipop | >| evel | | | printing | tInternal | >| | | | level for | | >| | | | the linear | | >| | | | solver MA86 | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_small | OT_REAL | 0.000 | Zero Pivot | CasADi::Ipop | >| | | | Threshold | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_static | OT_REAL | 0 | Static | CasADi::Ipop | >| | | | Pivoting | tInternal | >| | | | Threshold | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_u | OT_REAL | 0.000 | Pivoting | CasADi::Ipop | >| | | | Threshold | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_umax | OT_REAL | 0.000 | Maximum | CasADi::Ipop | >| | | | Pivoting | tInternal | >| | | | Threshold | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| magic_steps | OT_STRING | no | Enables | CasADi::Ipop | >| | | | magic steps. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_cpu_time | OT_REAL | 1000000 | Maximum | CasADi::Ipop | >| | | | number of | tInternal | >| | | | CPU seconds. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_filter_r | OT_INTEGER | 5 | Maximal | CasADi::Ipop | >| esets | | | allowed | tInternal | >| | | | number of | | >| | | | filter | | >| | | | resets (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_hessian_ | OT_REAL | 1.000e+20 | Maximum | CasADi::Ipop | >| perturbation | | | value of reg | tInternal | >| | | | ularization | | >| | | | parameter | | >| | | | for handling | | >| | | | negative | | >| | | | curvature. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter | OT_INTEGER | 3000 | Maximum | CasADi::Ipop | >| | | | number of | tInternal | >| | | | iterations. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_refineme | OT_INTEGER | 10 | Maximum | CasADi::Ipop | >| nt_steps | | | number of | tInternal | >| | | | iterative | | >| | | | refinement | | >| | | | steps per | | >| | | | linear | | >| | | | system | | >| | | | solve. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_resto_it | OT_INTEGER | 3000000 | Maximum | CasADi::Ipop | >| er | | | number of | tInternal | >| | | | successive | | >| | | | iterations | | >| | | | in | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_soc | OT_INTEGER | 4 | Maximum | CasADi::Ipop | >| | | | number of | tInternal | >| | | | second order | | >| | | | correction | | >| | | | trial steps | | >| | | | at each | | >| | | | iteration. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| max_soft_res | OT_INTEGER | 10 | Maximum | CasADi::Ipop | >| to_iters | | | number of | tInternal | >| | | | iterations | | >| | | | performed | | >| | | | successively | | >| | | | in soft | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| mehrotra_alg | OT_STRING | no | Indicates if | CasADi::Ipop | >| orithm | | | we want to | tInternal | >| | | | do | | >| | | | Mehrotra's | | >| | | | algorithm. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| min_alpha_pr | OT_REAL | 0.000 | LIFENG | CasADi::Ipop | >| imal | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| min_hessian_ | OT_REAL | 0.000 | Smallest | CasADi::Ipop | >| perturbation | | | perturbation | tInternal | >| | | | of the | | >| | | | Hessian | | >| | | | block. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| min_refineme | OT_INTEGER | 1 | Minimum | CasADi::Ipop | >| nt_steps | | | number of | tInternal | >| | | | iterative | | >| | | | refinement | | >| | | | steps per | | >| | | | linear | | >| | | | system | | >| | | | solve. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::Ipop | >| | | | uts) (eval_ | tInternal | >| | | | f|eval_g|eva | | >| | | | l_jac_g|eval | | >| | | | _grad_f|eval | | >| | | | _h) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_allow_fas | OT_STRING | yes | Allow | CasADi::Ipop | >| t_monotone_d | | | skipping of | tInternal | >| ecrease | | | barrier | | >| | | | problem if | | >| | | | barrier test | | >| | | | is already | | >| | | | met. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_init | OT_REAL | 0.100 | Initial | CasADi::Ipop | >| | | | value for | tInternal | >| | | | the barrier | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_linear_de | OT_REAL | 0.200 | Determines | CasADi::Ipop | >| crease_facto | | | linear | tInternal | >| r | | | decrease | | >| | | | rate of | | >| | | | barrier | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_max | OT_REAL | 100000 | Maximum | CasADi::Ipop | >| | | | value for | tInternal | >| | | | barrier | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_max_fact | OT_REAL | 1000 | Factor for i | CasADi::Ipop | >| | | | nitializatio | tInternal | >| | | | n of maximum | | >| | | | value for | | >| | | | barrier | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_min | OT_REAL | 0.000 | Minimum | CasADi::Ipop | >| | | | value for | tInternal | >| | | | barrier | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_oracle | OT_STRING | quality- | Oracle for a | CasADi::Ipop | >| | | function | new barrier | tInternal | >| | | | parameter in | | >| | | | the adaptive | | >| | | | strategy. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_strategy | OT_STRING | monotone | Update | CasADi::Ipop | >| | | | strategy for | tInternal | >| | | | barrier | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_superline | OT_REAL | 1.500 | Determines | CasADi::Ipop | >| ar_decrease_ | | | superlinear | tInternal | >| power | | | decrease | | >| | | | rate of | | >| | | | barrier | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mu_target | OT_REAL | 0 | Desired | CasADi::Ipop | >| | | | value of com | tInternal | >| | | | plementarity | | >| | | | . (see IPOPT | | >| | | | documentatio | | >| | | | n) | | >+--------------+--------------+--------------+--------------+--------------+ >| mult_diverg_ | OT_REAL | 0.000 | tolerance | CasADi::Ipop | >| feasibility_ | | | for deciding | tInternal | >| tol | | | if the | | >| | | | multipliers | | >| | | | are | | >| | | | diverging | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mult_diverg_ | OT_REAL | 100000000 | tolerance | CasADi::Ipop | >| y_tol | | | for deciding | tInternal | >| | | | if the | | >| | | | multipliers | | >| | | | are | | >| | | | diverging | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mumps_dep_to | OT_REAL | -1 | Pivot | CasADi::Ipop | >| l | | | threshold | tInternal | >| | | | for | | >| | | | detection of | | >| | | | linearly | | >| | | | dependent | | >| | | | constraints | | >| | | | in MUMPS. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mumps_mem_pe | OT_INTEGER | 1000 | Percentage | CasADi::Ipop | >| rcent | | | increase in | tInternal | >| | | | the | | >| | | | estimated | | >| | | | working | | >| | | | space for | | >| | | | MUMPS. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| mumps_permut | OT_INTEGER | 7 | Controls | CasADi::Ipop | >| ing_scaling | | | permuting | tInternal | >| | | | and scaling | | >| | | | in MUMPS | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mumps_pivot_ | OT_INTEGER | 7 | Controls | CasADi::Ipop | >| order | | | pivot order | tInternal | >| | | | in MUMPS | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| mumps_pivtol | OT_REAL | 0.000 | Pivot | CasADi::Ipop | >| | | | tolerance | tInternal | >| | | | for the | | >| | | | linear | | >| | | | solver | | >| | | | MUMPS. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| mumps_pivtol | OT_REAL | 0.100 | Maximum | CasADi::Ipop | >| max | | | pivot | tInternal | >| | | | tolerance | | >| | | | for the | | >| | | | linear | | >| | | | solver | | >| | | | MUMPS. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| mumps_scalin | OT_INTEGER | 77 | Controls | CasADi::Ipop | >| g | | | scaling in | tInternal | >| | | | MUMPS (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | CasADi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| neg_curv_tes | OT_REAL | 0 | Tolerance | CasADi::Ipop | >| t_tol | | | for | tInternal | >| | | | heuristic to | | >| | | | ignore wrong | | >| | | | inertia. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| never_use_fa | OT_STRING | no | Toggle to | CasADi::Ipop | >| ct_cgpen_dir | | | switch off | tInternal | >| ection | | | the fast | | >| | | | Chen- | | >| | | | Goldfarb | | >| | | | direction | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| never_use_pi | OT_STRING | no | Toggle to | CasADi::Ipop | >| ecewise_pena | | | switch off | tInternal | >| lty_ls | | | the | | >| | | | piecewise | | >| | | | penalty | | >| | | | method (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_lower_bo | OT_REAL | -1.000e+19 | any bound | CasADi::Ipop | >| und_inf | | | less or | tInternal | >| | | | equal this | | >| | | | value will | | >| | | | be | | >| | | | considered | | >| | | | -inf (i.e. | | >| | | | not lower | | >| | | | bounded). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_scaling_ | OT_REAL | 0 | Target value | CasADi::Ipop | >| constr_targe | | | for | tInternal | >| t_gradient | | | constraint | | >| | | | function | | >| | | | gradient | | >| | | | size. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_scaling_ | OT_REAL | 100 | Maximum | CasADi::Ipop | >| max_gradient | | | gradient | tInternal | >| | | | after NLP | | >| | | | scaling. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_scaling_ | OT_STRING | gradient- | Select the | CasADi::Ipop | >| method | | based | technique | tInternal | >| | | | used for | | >| | | | scaling the | | >| | | | NLP. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_scaling_ | OT_REAL | 0.000 | Minimum | CasADi::Ipop | >| min_value | | | value of | tInternal | >| | | | gradient- | | >| | | | based | | >| | | | scaling | | >| | | | values. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_scaling_ | OT_REAL | 0 | Target value | CasADi::Ipop | >| obj_target_g | | | for | tInternal | >| radient | | | objective | | >| | | | function | | >| | | | gradient | | >| | | | size. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_upper_bo | OT_REAL | 1.000e+19 | any bound | CasADi::Ipop | >| und_inf | | | greater or | tInternal | >| | | | this value | | >| | | | will be | | >| | | | considered | | >| | | | +inf (i.e. | | >| | | | not upper | | >| | | | bounded). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| nu_inc | OT_REAL | 0.000 | Increment of | CasADi::Ipop | >| | | | the penalty | tInternal | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| nu_init | OT_REAL | 0.000 | Initial | CasADi::Ipop | >| | | | value of the | tInternal | >| | | | penalty | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| num_linear_v | OT_INTEGER | 0 | Number of | CasADi::Ipop | >| ariables | | | linear | tInternal | >| | | | variables | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| obj_max_inc | OT_REAL | 5 | Determines | CasADi::Ipop | >| | | | the upper | tInternal | >| | | | bound on the | | >| | | | acceptable | | >| | | | increase of | | >| | | | barrier | | >| | | | objective | | >| | | | function. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| obj_scaling_ | OT_REAL | 1 | Scaling | CasADi::Ipop | >| factor | | | factor for | tInternal | >| | | | the | | >| | | | objective | | >| | | | function. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| option_file_ | OT_STRING | | File name of | CasADi::Ipop | >| name | | | options file | tInternal | >| | | | (to | | >| | | | overwrite | | >| | | | default). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| output_file | OT_STRING | | File name of | CasADi::Ipop | >| | | | desired | tInternal | >| | | | output file | | >| | | | (leave unset | | >| | | | for no file | | >| | | | output). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| parametric | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. | olverInterna | >| | | | Expect F, G, | l | >| | | | H, J to have | | >| | | | an | | >| | | | additional | | >| | | | input | | >| | | | argument | | >| | | | appended at | | >| | | | the end, | | >| | | | denoting | | >| | | | fixed | | >| | | | parameters. | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_INTEGER | 5000 | Maximum Size | CasADi::Ipop | >| _coarse_size | | | of Coarse | tInternal | >| | | | Grid Matrix | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_REAL | 0.500 | dropping | CasADi::Ipop | >| _dropping_fa | | | value for | tInternal | >| ctor | | | incomplete | | >| | | | factor (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_REAL | 0.100 | dropping | CasADi::Ipop | >| _dropping_sc | | | value for | tInternal | >| hur | | | sparsify | | >| | | | schur | | >| | | | complement | | >| | | | factor (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_REAL | 5000000 | (see IPOPT d | CasADi::Ipop | >| _inverse_nor | | | ocumentation | tInternal | >| m_factor | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_INTEGER | 10 | Maximum Size | CasADi::Ipop | >| _max_levels | | | of Grid | tInternal | >| | | | Levels (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_INTEGER | 10000000 | max fill for | CasADi::Ipop | >| _max_row_fil | | | each row | tInternal | >| l | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_REAL | 0.000 | Relative | CasADi::Ipop | >| _relative_to | | | Residual | tInternal | >| l | | | Convergence | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_iter | OT_STRING | no | Switch on | CasADi::Ipop | >| ative | | | iterative | tInternal | >| | | | solver in | | >| | | | Pardiso | | >| | | | library (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_matc | OT_STRING | complete+2x2 | Matching | CasADi::Ipop | >| hing_strateg | | | strategy to | tInternal | >| y | | | be used by | | >| | | | Pardiso (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_max_ | OT_INTEGER | 4 | Maximal | CasADi::Ipop | >| droptol_corr | | | number of | tInternal | >| ections | | | decreases of | | >| | | | drop | | >| | | | tolerance | | >| | | | during one | | >| | | | solve. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_max_ | OT_INTEGER | 500 | Maximum | CasADi::Ipop | >| iter | | | number of | tInternal | >| | | | Krylov- | | >| | | | Subspace | | >| | | | Iteration | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_msgl | OT_INTEGER | 0 | Pardiso | CasADi::Ipop | >| vl | | | message | tInternal | >| | | | level (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_out_ | OT_INTEGER | 0 | Enables out- | CasADi::Ipop | >| of_core_powe | | | of-core | tInternal | >| r | | | variant of | | >| | | | Pardiso (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_redo | OT_STRING | no | Toggle for | CasADi::Ipop | >| _symbolic_fa | | | handling | tInternal | >| ct_only_if_i | | | case when | | >| nertia_wrong | | | elements | | >| | | | were | | >| | | | perturbed by | | >| | | | Pardiso. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_repe | OT_STRING | no | Interpretati | CasADi::Ipop | >| ated_perturb | | | on of | tInternal | >| ation_means_ | | | perturbed | | >| singular | | | elements. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pardiso_skip | OT_STRING | no | Always | CasADi::Ipop | >| _inertia_che | | | pretend | tInternal | >| ck | | | inertia is | | >| | | | correct. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pass_nonline | OT_BOOLEAN | False | n/a | CasADi::Ipop | >| ar_variables | | | | tInternal | >+--------------+--------------+--------------+--------------+--------------+ >| pen_des_fact | OT_REAL | 0.200 | a parameter | CasADi::Ipop | >| | | | used in | tInternal | >| | | | penalty | | >| | | | parameter | | >| | | | computation | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| pen_init_fac | OT_REAL | 50 | a parameter | CasADi::Ipop | >| | | | used to | tInternal | >| | | | choose | | >| | | | initial | | >| | | | penalty para | | >| | | | meterswhen | | >| | | | the | | >| | | | regularized | | >| | | | Newton | | >| | | | method is | | >| | | | used. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| pen_theta_ma | OT_REAL | 10000 | Determines | CasADi::Ipop | >| x_fact | | | upper bound | tInternal | >| | | | for | | >| | | | constraint | | >| | | | violation in | | >| | | | the filter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| penalty_init | OT_REAL | 100000 | Maximal | CasADi::Ipop | >| _max | | | value for | tInternal | >| | | | the intial | | >| | | | penalty | | >| | | | parameter | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| penalty_init | OT_REAL | 1 | Minimal | CasADi::Ipop | >| _min | | | value for | tInternal | >| | | | the intial | | >| | | | penalty | | >| | | | parameter | | >| | | | for line | | >| | | | search(for | | >| | | | Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| penalty_max | OT_REAL | 1.000e+30 | Maximal | CasADi::Ipop | >| | | | value for | tInternal | >| | | | the penalty | | >| | | | parameter | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| penalty_upda | OT_REAL | 10 | LIFENG | CasADi::Ipop | >| te_compl_tol | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| penalty_upda | OT_REAL | 0.000 | Threshold | CasADi::Ipop | >| te_infeasibi | | | for infeasib | tInternal | >| lity_tol | | | ility in | | >| | | | penalty | | >| | | | parameter | | >| | | | update test. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| perturb_alwa | OT_STRING | no | Active | CasADi::Ipop | >| ys_cd | | | permanent | tInternal | >| | | | perturbation | | >| | | | of | | >| | | | constraint l | | >| | | | inearization | | >| | | | . (see IPOPT | | >| | | | documentatio | | >| | | | n) | | >+--------------+--------------+--------------+--------------+--------------+ >| perturb_dec_ | OT_REAL | 0.333 | Decrease | CasADi::Ipop | >| fact | | | factor for | tInternal | >| | | | x-s perturba | | >| | | | tion. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| perturb_inc_ | OT_REAL | 8 | Increase | CasADi::Ipop | >| fact | | | factor for | tInternal | >| | | | x-s perturba | | >| | | | tion. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| perturb_inc_ | OT_REAL | 100 | Increase | CasADi::Ipop | >| fact_first | | | factor for | tInternal | >| | | | x-s | | >| | | | perturbation | | >| | | | for very | | >| | | | first pertur | | >| | | | bation. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| piecewisepen | OT_REAL | 0.000 | LIFENG | CasADi::Ipop | >| alty_gamma_i | | | WRITES THIS. | tInternal | >| nfeasi | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| piecewisepen | OT_REAL | 0.000 | LIFENG | CasADi::Ipop | >| alty_gamma_o | | | WRITES THIS. | tInternal | >| bj | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| point_pertur | OT_REAL | 10 | Maximal | CasADi::Ipop | >| bation_radiu | | | perturbation | tInternal | >| s | | | of an | | >| | | | evaluation | | >| | | | point. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| print_info_s | OT_STRING | no | Enables | CasADi::Ipop | >| tring | | | printing of | tInternal | >| | | | additional | | >| | | | info string | | >| | | | at end of | | >| | | | iteration | | >| | | | output. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| print_level | OT_INTEGER | 5 | Output | CasADi::Ipop | >| | | | verbosity | tInternal | >| | | | level. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| print_option | OT_STRING | no | Switch to | CasADi::Ipop | >| s_documentat | | | print all | tInternal | >| ion | | | algorithmic | | >| | | | options. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| print_option | OT_STRING | no | Undocumented | CasADi::Ipop | >| s_latex_mode | | | (see IPOPT d | tInternal | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| print_time | OT_BOOLEAN | True | print | CasADi::Ipop | >| | | | information | tInternal | >| | | | about | | >| | | | execution | | >| | | | time | | >+--------------+--------------+--------------+--------------+--------------+ >| print_timing | OT_STRING | no | Switch to | CasADi::Ipop | >| _statistics | | | print timing | tInternal | >| | | | statistics. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| print_user_o | OT_STRING | no | Print all | CasADi::Ipop | >| ptions | | | options set | tInternal | >| | | | by the user. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| quality_func | OT_STRING | none | The | CasADi::Ipop | >| tion_balanci | | | balancing | tInternal | >| ng_term | | | term | | >| | | | included in | | >| | | | the quality | | >| | | | function for | | >| | | | centrality. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| quality_func | OT_STRING | none | The penalty | CasADi::Ipop | >| tion_central | | | term for | tInternal | >| ity | | | centrality | | >| | | | that is | | >| | | | included in | | >| | | | quality | | >| | | | function. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| quality_func | OT_INTEGER | 8 | Maximum | CasADi::Ipop | >| tion_max_sec | | | number of | tInternal | >| tion_steps | | | search steps | | >| | | | during | | >| | | | direct | | >| | | | search | | >| | | | procedure | | >| | | | determining | | >| | | | the optimal | | >| | | | centering | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| quality_func | OT_STRING | 2-norm- | Norm used | CasADi::Ipop | >| tion_norm_ty | | squared | for | tInternal | >| pe | | | components | | >| | | | of the | | >| | | | quality | | >| | | | function. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| quality_func | OT_REAL | 0 | Tolerance | CasADi::Ipop | >| tion_section | | | for the | tInternal | >| _qf_tol | | | golden | | >| | | | section | | >| | | | search | | >| | | | procedure | | >| | | | determining | | >| | | | the optimal | | >| | | | centering | | >| | | | parameter | | >| | | | (in the | | >| | | | function | | >| | | | value | | >| | | | space). (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| quality_func | OT_REAL | 0.010 | Tolerance | CasADi::Ipop | >| tion_section | | | for the | tInternal | >| _sigma_tol | | | section | | >| | | | search | | >| | | | procedure | | >| | | | determining | | >| | | | the optimal | | >| | | | centering | | >| | | | parameter | | >| | | | (in sigma | | >| | | | space). (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| recalc_y | OT_STRING | no | Tells the | CasADi::Ipop | >| | | | algorithm to | tInternal | >| | | | recalculate | | >| | | | the equality | | >| | | | and | | >| | | | inequality | | >| | | | multipliers | | >| | | | as least | | >| | | | square | | >| | | | estimates. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| recalc_y_fea | OT_REAL | 0.000 | Feasibility | CasADi::Ipop | >| s_tol | | | threshold | tInternal | >| | | | for recomput | | >| | | | ation of | | >| | | | multipliers. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| replace_boun | OT_STRING | no | Indicates if | CasADi::Ipop | >| ds | | | all variable | tInternal | >| | | | bounds | | >| | | | should be | | >| | | | replaced by | | >| | | | inequality | | >| | | | constraints | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| required_inf | OT_REAL | 0.900 | Required | CasADi::Ipop | >| easibility_r | | | reduction of | tInternal | >| eduction | | | infeasibilit | | >| | | | y before | | >| | | | leaving | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| residual_imp | OT_REAL | 1.000 | Minimal | CasADi::Ipop | >| rovement_fac | | | required | tInternal | >| tor | | | reduction of | | >| | | | residual | | >| | | | test ratio | | >| | | | in iterative | | >| | | | refinement. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| residual_rat | OT_REAL | 0.000 | Iterative | CasADi::Ipop | >| io_max | | | refinement | tInternal | >| | | | tolerance | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| residual_rat | OT_REAL | 0.000 | Threshold | CasADi::Ipop | >| io_singular | | | for | tInternal | >| | | | declaring | | >| | | | linear | | >| | | | system | | >| | | | singular | | >| | | | after failed | | >| | | | iterative | | >| | | | refinement. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| resto_failur | OT_REAL | 0 | Threshold | CasADi::Ipop | >| e_feasibilit | | | for primal i | tInternal | >| y_threshold | | | nfeasibility | | >| | | | to declare | | >| | | | failure of | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| resto_penalt | OT_REAL | 1000 | Penalty | CasADi::Ipop | >| y_parameter | | | parameter in | tInternal | >| | | | the | | >| | | | restoration | | >| | | | phase | | >| | | | objective | | >| | | | function. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| resto_proxim | OT_REAL | 1 | Weighting | CasADi::Ipop | >| ity_weight | | | factor for | tInternal | >| | | | the | | >| | | | proximity | | >| | | | term in | | >| | | | restoration | | >| | | | phase | | >| | | | objective. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| rho | OT_REAL | 0.100 | Value in | CasADi::Ipop | >| | | | penalty | tInternal | >| | | | parameter | | >| | | | update | | >| | | | formula. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| s_max | OT_REAL | 100 | Scaling | CasADi::Ipop | >| | | | threshold | tInternal | >| | | | for the NLP | | >| | | | error. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| s_phi | OT_REAL | 2.300 | Exponent for | CasADi::Ipop | >| | | | linear | tInternal | >| | | | barrier | | >| | | | function | | >| | | | model in the | | >| | | | switching | | >| | | | rule. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| s_theta | OT_REAL | 1.100 | Exponent for | CasADi::Ipop | >| | | | current | tInternal | >| | | | constraint | | >| | | | violation in | | >| | | | the | | >| | | | switching | | >| | | | rule. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| sb | OT_STRING | no | (see IPOPT d | CasADi::Ipop | >| | | | ocumentation | tInternal | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| sigma_max | OT_REAL | 100 | Maximum | CasADi::Ipop | >| | | | value of the | tInternal | >| | | | centering | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| sigma_min | OT_REAL | 0.000 | Minimum | CasADi::Ipop | >| | | | value of the | tInternal | >| | | | centering | | >| | | | parameter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| skip_corr_if | OT_STRING | yes | Skip the | CasADi::Ipop | >| _neg_curv | | | corrector | tInternal | >| | | | step in | | >| | | | negative | | >| | | | curvature | | >| | | | iteration (u | | >| | | | nsupported!) | | >| | | | . (see IPOPT | | >| | | | documentatio | | >| | | | n) | | >+--------------+--------------+--------------+--------------+--------------+ >| skip_corr_in | OT_STRING | yes | Skip the | CasADi::Ipop | >| _monotone_mo | | | corrector | tInternal | >| de | | | step during | | >| | | | monotone | | >| | | | barrier | | >| | | | parameter | | >| | | | mode (unsupp | | >| | | | orted!). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| skip_finaliz | OT_STRING | no | Indicates if | CasADi::Ipop | >| e_solution_c | | | call to NLP: | tInternal | >| all | | | :FinalizeSol | | >| | | | ution after | | >| | | | optimization | | >| | | | should be | | >| | | | suppressed | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| slack_bound_ | OT_REAL | 0.010 | Desired | CasADi::Ipop | >| frac | | | minimum | tInternal | >| | | | relative | | >| | | | distance | | >| | | | from the | | >| | | | initial | | >| | | | slack to | | >| | | | bound. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| slack_bound_ | OT_REAL | 0.010 | Desired | CasADi::Ipop | >| push | | | minimum | tInternal | >| | | | absolute | | >| | | | distance | | >| | | | from the | | >| | | | initial | | >| | | | slack to | | >| | | | bound. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| slack_move | OT_REAL | 0.000 | Correction | CasADi::Ipop | >| | | | size for | tInternal | >| | | | very small | | >| | | | slacks. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| soft_resto_p | OT_REAL | 1.000 | Required | CasADi::Ipop | >| derror_reduc | | | reduction in | tInternal | >| tion_factor | | | primal-dual | | >| | | | error in the | | >| | | | soft | | >| | | | restoration | | >| | | | phase. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| start_with_r | OT_STRING | no | Tells | CasADi::Ipop | >| esto | | | algorithm to | tInternal | >| | | | switch to | | >| | | | restoration | | >| | | | phase in | | >| | | | first | | >| | | | iteration. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| suppress_all | OT_STRING | no | Undocumented | CasADi::Ipop | >| _output | | | (see IPOPT d | tInternal | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| tau_min | OT_REAL | 0.990 | Lower bound | CasADi::Ipop | >| | | | on fraction- | tInternal | >| | | | to-the- | | >| | | | boundary | | >| | | | parameter | | >| | | | tau. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| theta_max_fa | OT_REAL | 10000 | Determines | CasADi::Ipop | >| ct | | | upper bound | tInternal | >| | | | for | | >| | | | constraint | | >| | | | violation in | | >| | | | the filter. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| theta_min | OT_REAL | 0.000 | LIFENG | CasADi::Ipop | >| | | | WRITES THIS. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| theta_min_fa | OT_REAL | 0.000 | Determines | CasADi::Ipop | >| ct | | | constraint | tInternal | >| | | | violation | | >| | | | threshold in | | >| | | | the | | >| | | | switching | | >| | | | rule. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| tiny_step_to | OT_REAL | 0.000 | Tolerance | CasADi::Ipop | >| l | | | for | tInternal | >| | | | detecting | | >| | | | numerically | | >| | | | insignifican | | >| | | | t steps. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| tiny_step_y_ | OT_REAL | 0.010 | Tolerance | CasADi::Ipop | >| tol | | | for quitting | tInternal | >| | | | because of | | >| | | | numerically | | >| | | | insignifican | | >| | | | t steps. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| tol | OT_REAL | 0.000 | Desired | CasADi::Ipop | >| | | | convergence | tInternal | >| | | | tolerance | | >| | | | (relative). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | CasADi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| var_integer_ | OT_DICTIONAR | None | Integer | CasADi::Ipop | >| md | Y | | metadata (a | tInternal | >| | | | dictionary | | >| | | | with lists | | >| | | | of integers) | | >| | | | about | | >| | | | variables to | | >| | | | be passed to | | >| | | | IPOPT | | >+--------------+--------------+--------------+--------------+--------------+ >| var_numeric_ | OT_DICTIONAR | None | Numeric | CasADi::Ipop | >| md | Y | | metadata (a | tInternal | >| | | | dictionary | | >| | | | with lists | | >| | | | of reals) | | >| | | | about | | >| | | | variables to | | >| | | | be passed to | | >| | | | IPOPT | | >+--------------+--------------+--------------+--------------+--------------+ >| var_string_m | OT_DICTIONAR | None | String | CasADi::Ipop | >| d | Y | | metadata (a | tInternal | >| | | | dictionary | | >| | | | with lists | | >| | | | of strings) | | >| | | | about | | >| | | | variables to | | >| | | | be passed to | | >| | | | IPOPT | | >+--------------+--------------+--------------+--------------+--------------+ >| vartheta | OT_REAL | 0.500 | a parameter | CasADi::Ipop | >| | | | used to | tInternal | >| | | | check if the | | >| | | | fast | | >| | | | direction | | >| | | | can be used | | >| | | | asthe line | | >| | | | search | | >| | | | direction | | >| | | | (for Chen- | | >| | | | Goldfarb | | >| | | | line | | >| | | | search). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | CasADi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_b | OT_REAL | 0.001 | same as | CasADi::Ipop | >| ound_frac | | | bound_frac | tInternal | >| | | | for the | | >| | | | regular | | >| | | | initializer. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_b | OT_REAL | 0.001 | same as | CasADi::Ipop | >| ound_push | | | bound_push | tInternal | >| | | | for the | | >| | | | regular | | >| | | | initializer. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_e | OT_STRING | no | Tells | CasADi::Ipop | >| ntire_iterat | | | algorithm | tInternal | >| e | | | whether to | | >| | | | use the GetW | | >| | | | armStartIter | | >| | | | ate method | | >| | | | in the NLP. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_i | OT_STRING | no | Warm-start | CasADi::Ipop | >| nit_point | | | for initial | tInternal | >| | | | point (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_m | OT_REAL | 0.001 | same as mult | CasADi::Ipop | >| ult_bound_pu | | | _bound_push | tInternal | >| sh | | | for the | | >| | | | regular | | >| | | | initializer. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_m | OT_REAL | 1000000 | Maximum | CasADi::Ipop | >| ult_init_max | | | initial | tInternal | >| | | | value for | | >| | | | the equality | | >| | | | multipliers. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_s | OT_STRING | no | Indicates | CasADi::Ipop | >| ame_structur | | | whether a | tInternal | >| e | | | problem with | | >| | | | a structure | | >| | | | identical to | | >| | | | the previous | | >| | | | one is to be | | >| | | | solved. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_s | OT_REAL | 0.001 | same as slac | CasADi::Ipop | >| lack_bound_f | | | k_bound_frac | tInternal | >| rac | | | for the | | >| | | | regular | | >| | | | initializer. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_s | OT_REAL | 0.001 | same as slac | CasADi::Ipop | >| lack_bound_p | | | k_bound_push | tInternal | >| ush | | | for the | | >| | | | regular | | >| | | | initializer. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warm_start_t | OT_REAL | 0 | Unsupported! | CasADi::Ipop | >| arget_mu | | | (see IPOPT d | tInternal | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| warn_initial | OT_BOOLEAN | false | Warn if the | CasADi::NLPS | >| _bounds | | | initial | olverInterna | >| | | | guess does | l | >| | | | not satisfy | | >| | | | LBX and UBX | | >+--------------+--------------+--------------+--------------+--------------+ >| watchdog_sho | OT_INTEGER | 10 | Number of | CasADi::Ipop | >| rtened_iter_ | | | shortened | tInternal | >| trigger | | | iterations | | >| | | | that trigger | | >| | | | the | | >| | | | watchdog. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| watchdog_tri | OT_INTEGER | 3 | Maximum | CasADi::Ipop | >| al_iter_max | | | number of | tInternal | >| | | | watchdog | | >| | | | iterations. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_inexact | OT_REAL | 0 | Drop | CasADi::Ipop | >| _droptol | | | tolerance | tInternal | >| | | | for inexact | | >| | | | factorizatio | | >| | | | n preconditi | | >| | | | oner in | | >| | | | WISMP. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_inexact | OT_REAL | 0 | Fill-in | CasADi::Ipop | >| _fillin_limi | | | limit for | tInternal | >| t | | | inexact fact | | >| | | | orization pr | | >| | | | econditioner | | >| | | | in WISMP. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_iterati | OT_STRING | no | Switches to | CasADi::Ipop | >| ve | | | iterative | tInternal | >| | | | solver in | | >| | | | WSMP. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_max_ite | OT_INTEGER | 1000 | Maximal | CasADi::Ipop | >| r | | | number of | tInternal | >| | | | iterations | | >| | | | in iterative | | >| | | | WISMP (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_no_pivo | OT_STRING | no | Use the | CasADi::Ipop | >| ting | | | static | tInternal | >| | | | pivoting | | >| | | | option of | | >| | | | WSMP. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_num_thr | OT_INTEGER | 1 | Number of | CasADi::Ipop | >| eads | | | threads to | tInternal | >| | | | be used in | | >| | | | WSMP (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_orderin | OT_INTEGER | 1 | Determines | CasADi::Ipop | >| g_option | | | how ordering | tInternal | >| | | | is done in | | >| | | | WSMP | | >| | | | (IPARM(16) | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_orderin | OT_INTEGER | 1 | Determines | CasADi::Ipop | >| g_option2 | | | how ordering | tInternal | >| | | | is done in | | >| | | | WSMP | | >| | | | (IPARM(20) | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_pivtol | OT_REAL | 0.000 | Pivot | CasADi::Ipop | >| | | | tolerance | tInternal | >| | | | for the | | >| | | | linear | | >| | | | solver WSMP. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_pivtolm | OT_REAL | 0.100 | Maximum | CasADi::Ipop | >| ax | | | pivot | tInternal | >| | | | tolerance | | >| | | | for the | | >| | | | linear | | >| | | | solver WSMP. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_scaling | OT_INTEGER | 0 | Determines | CasADi::Ipop | >| | | | how the | tInternal | >| | | | matrix is | | >| | | | scaled by | | >| | | | WSMP. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_singula | OT_REAL | 0.000 | WSMP's | CasADi::Ipop | >| rity_thresho | | | singularity | tInternal | >| ld | | | threshold. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_skip_in | OT_STRING | no | Always | CasADi::Ipop | >| ertia_check | | | pretent | tInternal | >| | | | inertia is | | >| | | | correct. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| wsmp_write_m | OT_INTEGER | -1 | Iteration in | CasADi::Ipop | >| atrix_iterat | | | which the | tInternal | >| ion | | | matrices are | | >| | | | written to | | >| | | | files. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available monitors >+-------------+--------------------------+ >| Id | Used in | >+=============+==========================+ >| eval_f | CasADi::IpoptInternal | >+-------------+--------------------------+ >| eval_g | CasADi::IpoptInternal | >+-------------+--------------------------+ >| eval_grad_f | CasADi::IpoptInternal | >+-------------+--------------------------+ >| eval_h | CasADi::IpoptInternal | >+-------------+--------------------------+ >| eval_jac_g | CasADi::IpoptInternal | >+-------------+--------------------------+ >| inputs | CasADi::FunctionInternal | >+-------------+--------------------------+ >| outputs | CasADi::FunctionInternal | >+-------------+--------------------------+ > >>List of available stats >+--------------------+-----------------------+ >| Id | Used in | >+====================+=======================+ >| con_integer_md | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| con_numeric_md | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| con_string_md | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| iter_count | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| iteration | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| iterations | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| n_eval_f | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| n_eval_g | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| n_eval_grad_f | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| n_eval_h | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| n_eval_jac_g | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| return_status | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_callback_fun | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_callback_prepare | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_eval_f | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_eval_g | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_eval_grad_f | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_eval_h | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_eval_jac_g | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| t_mainloop | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| var_integer_md | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| var_numeric_md | CasADi::IpoptInternal | >+--------------------+-----------------------+ >| var_string_md | CasADi::IpoptInternal | >+--------------------+-----------------------+ > >Diagrams > >C++ includes: ipopt_solver.hpp -} newtype IpoptSolver = IpoptSolver (ForeignPtr IpoptSolver') -- typeclass decl class IpoptSolverClass a where castIpoptSolver :: a -> IpoptSolver instance IpoptSolverClass IpoptSolver where castIpoptSolver = id -- baseclass instances instance SharedObjectClass IpoptSolver where castSharedObject (IpoptSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass IpoptSolver where castPrintableObject (IpoptSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass IpoptSolver where castOptionsFunctionality (IpoptSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass IpoptSolver where castFunction (IpoptSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass IpoptSolver where castIOInterfaceFunction (IpoptSolver x) = IOInterfaceFunction (castForeignPtr x) instance NLPSolverClass IpoptSolver where castNLPSolver (IpoptSolver x) = NLPSolver (castForeignPtr x) -- helper instances instance Marshal IpoptSolver (Ptr IpoptSolver') where marshal (IpoptSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (IpoptSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__IpoptSolver" c_delete_CasADi__IpoptSolver :: FunPtr (Ptr IpoptSolver' -> IO ()) instance WrapReturn (Ptr IpoptSolver') IpoptSolver where wrapReturn = (fmap IpoptSolver) . (newForeignPtr c_delete_CasADi__IpoptSolver) -- raw decl data DMatrix' -- data decl {-| >[INTERNAL] Sparse matrix class. SX >and DMatrix are specializations. > >General sparse matrix class that is designed with the idea that "everything >is a matrix", that is, also scalars and vectors. This philosophy makes it >easy to use and to interface in particularily with Python and Matlab/Octave. >Index starts with 0. Index vec happens as follows: (rr,cc) -> k = >rr+cc*size1() Vectors are column vectors. The storage format is Compressed >Column Storage (CCS), similar to that used for sparse matrices in Matlab, >but unlike this format, we do allow for elements to be structurally non-zero >but numerically zero. Matrix is polymorphic with a >std::vector that contain all non- identical-zero elements. The >sparsity can be accessed with Sparsity& sparsity() Joel Andersson > >C++ includes: casadi_types.hpp -} 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) instance ExpDMatrixClass DMatrix where castExpDMatrix (DMatrix x) = ExpDMatrix (castForeignPtr x) instance GenDMatrixClass DMatrix where castGenDMatrix (DMatrix x) = GenDMatrix (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__Matrix_double_" c_delete_CasADi__Matrix_double_ :: FunPtr (Ptr DMatrix' -> IO ()) instance WrapReturn (Ptr DMatrix') DMatrix where wrapReturn = (fmap DMatrix) . (newForeignPtr c_delete_CasADi__Matrix_double_) -- raw decl data Sparsity' -- data decl {-| >[INTERNAL] 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 fulfils: >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 SharedObjectClass Sparsity where castSharedObject (Sparsity x) = SharedObject (castForeignPtr x) instance PrintableObjectClass Sparsity where castPrintableObject (Sparsity x) = PrintableObject (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 ExpMX' -- data decl {-| >[INTERNAL] Expression >interface. > >This is a common base class for SX, MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. Joel Andersson > >C++ includes: generic_expression.hpp -} newtype ExpMX = ExpMX (ForeignPtr ExpMX') -- typeclass decl class ExpMXClass a where castExpMX :: a -> ExpMX instance ExpMXClass ExpMX where castExpMX = id -- baseclass instances -- helper instances instance Marshal ExpMX (Ptr ExpMX') where marshal (ExpMX x) = return (unsafeForeignPtrToPtr x) marshalFree (ExpMX x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericExpression_CasADi__MX_" c_delete_CasADi__GenericExpression_CasADi__MX_ :: FunPtr (Ptr ExpMX' -> IO ()) instance WrapReturn (Ptr ExpMX') ExpMX where wrapReturn = (fmap ExpMX) . (newForeignPtr c_delete_CasADi__GenericExpression_CasADi__MX_) -- raw decl data MX' -- data decl {-| >[INTERNAL] MX - Matrix expression. > >The MX class is used to build up trees made up from MXNodes. It is a more >general graph representation than the scalar expression, SX, and much less >efficient for small objects. On the other hand, the class allows much more >general operations than does SX, in particular matrix valued operations and >calls to arbitrary differentiable functions. > >The MX class is designed to have identical syntax with the Matrix<> template >class, and uses Matrix as its internal representation of the values >at a node. By keeping the syntaxes identical, it is possible to switch from >one class to the other, as well as inlining MX functions to SXElement >functions. > >Note that an operation is always "lazy", making a matrix multiplication >will create a matrix multiplication node, not perform the actual >multiplication. > >Joel Andersson > >C++ includes: mx.hpp -} newtype MX = MX (ForeignPtr MX') -- typeclass decl class MXClass a where castMX :: a -> MX instance MXClass MX where castMX = id -- baseclass instances instance SharedObjectClass MX where castSharedObject (MX x) = SharedObject (castForeignPtr x) instance PrintableObjectClass MX where castPrintableObject (MX x) = PrintableObject (castForeignPtr x) instance ExpMXClass MX where castExpMX (MX x) = ExpMX (castForeignPtr x) instance GenMXClass MX where castGenMX (MX x) = GenMX (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 QCQPStructure' -- data decl {-| >[INTERNAL] Helper >function for 'QCQPStruct' > >C++ includes: casadi_types.hpp -} newtype QCQPStructure = QCQPStructure (ForeignPtr QCQPStructure') -- typeclass decl class QCQPStructureClass a where castQCQPStructure :: a -> QCQPStructure instance QCQPStructureClass QCQPStructure where castQCQPStructure = id -- baseclass instances instance PrintableObjectClass QCQPStructure where castPrintableObject (QCQPStructure x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal QCQPStructure (Ptr QCQPStructure') where marshal (QCQPStructure x) = return (unsafeForeignPtrToPtr x) marshalFree (QCQPStructure x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__QCQPStructIOSchemeVector_CasADi__Sparsity_" c_delete_CasADi__QCQPStructIOSchemeVector_CasADi__Sparsity_ :: FunPtr (Ptr QCQPStructure' -> IO ()) instance WrapReturn (Ptr QCQPStructure') QCQPStructure where wrapReturn = (fmap QCQPStructure) . (newForeignPtr c_delete_CasADi__QCQPStructIOSchemeVector_CasADi__Sparsity_) -- raw decl data DpleSolver' -- data decl {-| >[INTERNAL] Base class for >Discrete Periodic Lyapunov Equation Solvers. > >Given matrices A_k and symmetric V_k, k = 0..K-1 > >A_k in R^(n x n) V_k in R^n > >provides all of P_k that satisfy: > >P_0 = A_(K-1)*P_(K-1)*A_(K-1)' + V_k P_k+1 = A_k*P_k*A_k' + V_k for k = >1..K-1 Joris gillis > >>Input scheme: CasADi::DPLEInput (DPLE_NUM_IN = 3) [dpleIn] >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| DPLE_A | a | A matrices (horzcat | >| | | when const_dim, | >| | | blkdiag otherwise) . | >+------------------------+------------------------+------------------------+ >| DPLE_V | v | V matrices (horzcat | >| | | when const_dim, | >| | | blkdiag otherwise) . | >+------------------------+------------------------+------------------------+ > >>Output scheme: CasADi::DPLEOutput (DPLE_NUM_OUT = 2) [dpleOut] >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| DPLE_P | p | Lyapunov matrix | >| | | (horzcat when | >| | | const_dim, blkdiag | >| | | otherwise) (cholesky | >| | | of P if pos_def) . | >+------------------------+------------------------+------------------------+ > >>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) | | >+--------------+--------------+--------------+--------------+--------------+ >| const_dim | OT_BOOLEAN | true | Assume | CasADi::Dple | >| | | | constant | Internal | >| | | | dimension of | | >| | | | P | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| eps_unstable | OT_REAL | 0.000 | A margin for | CasADi::Dple | >| | | | unstability | Internal | >| | | | detection | | >+--------------+--------------+--------------+--------------+--------------+ >| error_unstab | OT_BOOLEAN | false | Throw an | CasADi::Dple | >| le | | | exception | Internal | >| | | | when it is | | >| | | | detected | | >| | | | that Product | | >| | | | (A_i,i=N..1) | | >| | | | has | | >| | | | eigenvalues | | >| | | | greater than | | >| | | | 1-eps_unstab | | >| | | | le | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| pos_def | OT_BOOLEAN | false | Assume P | CasADi::Dple | >| | | | positive | Internal | >| | | | definite | | >+--------------+--------------+--------------+--------------+--------------+ >| 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: dple_solver.hpp -} newtype DpleSolver = DpleSolver (ForeignPtr DpleSolver') -- typeclass decl class DpleSolverClass a where castDpleSolver :: a -> DpleSolver instance DpleSolverClass DpleSolver where castDpleSolver = id -- baseclass instances instance SharedObjectClass DpleSolver where castSharedObject (DpleSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass DpleSolver where castPrintableObject (DpleSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass DpleSolver where castOptionsFunctionality (DpleSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass DpleSolver where castFunction (DpleSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass DpleSolver where castIOInterfaceFunction (DpleSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal DpleSolver (Ptr DpleSolver') where marshal (DpleSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (DpleSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__DpleSolver" c_delete_CasADi__DpleSolver :: FunPtr (Ptr DpleSolver' -> IO ()) instance WrapReturn (Ptr DpleSolver') DpleSolver where wrapReturn = (fmap DpleSolver) . (newForeignPtr c_delete_CasADi__DpleSolver) -- raw decl data SDQPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass SDQPSolver where castSharedObject (SDQPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SDQPSolver where castPrintableObject (SDQPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SDQPSolver where castOptionsFunctionality (SDQPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SDQPSolver where castFunction (SDQPSolver x) = Function (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 QPLPSolver' -- data decl {-| >[INTERNAL] IPOPT QP Solver for >quadratic programming. > >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 | >| | | | wether | | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver | OT_QPSOLVER | GenericType( | The QPSOlver | CasADi::QPLP | >| | | ) | used to | Internal | >| | | | solve the | | >| | | | LPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver_op | OT_DICTIONAR | GenericType( | Options to | CasADi::QPLP | >| tions | Y | ) | be passed to | Internal | >| | | | the QPSOlver | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+=================+======================+ >| qp_solver_stats | CasADi::QPLPInternal | >+-----------------+----------------------+ > >Diagrams > >C++ includes: qp_lp_solver.hpp -} newtype QPLPSolver = QPLPSolver (ForeignPtr QPLPSolver') -- typeclass decl class QPLPSolverClass a where castQPLPSolver :: a -> QPLPSolver instance QPLPSolverClass QPLPSolver where castQPLPSolver = id -- baseclass instances instance SharedObjectClass QPLPSolver where castSharedObject (QPLPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass QPLPSolver where castPrintableObject (QPLPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass QPLPSolver where castOptionsFunctionality (QPLPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass QPLPSolver where castFunction (QPLPSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass QPLPSolver where castIOInterfaceFunction (QPLPSolver x) = IOInterfaceFunction (castForeignPtr x) instance LPSolverClass QPLPSolver where castLPSolver (QPLPSolver x) = LPSolver (castForeignPtr x) -- helper instances instance Marshal QPLPSolver (Ptr QPLPSolver') where marshal (QPLPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (QPLPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__QPLPSolver" c_delete_CasADi__QPLPSolver :: FunPtr (Ptr QPLPSolver' -> IO ()) instance WrapReturn (Ptr QPLPSolver') QPLPSolver where wrapReturn = (fmap QPLPSolver) . (newForeignPtr c_delete_CasADi__QPLPSolver) -- raw decl data SDPSDQPSolver' -- data decl {-| >[INTERNAL] SDP SDQP Solver >for quadratic programming. > >Note: this implementation relies on Cholesky decomposition: Chol(H) = L -> H >= LL' with L lower triangular This requires Pi, H to be positive definite. >Positive semi-definite is not sufficient. Notably, H==0 will not work. > >A better implementation would rely on matrix square root, but we need >singular value decomposition to implement that. > >Same as an SDPSolver, but with a quadratic objective 1/2 x' H x > >Joris Gillis > >>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 | >| | | | wether | | >| | | | 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::SDPS | >| | | ) | SDPSolver | DQPInternal | >| | | | used to | | >| | | | solve the | | >| | | | SDQPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| sdp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::SDPS | >| ptions | Y | ) | be passed to | DQPInternal | >| | | | the | | >| | | | SDPSOlver | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | CasADi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | CasADi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available stats >+------------------+-------------------------+ >| Id | Used in | >+==================+=========================+ >| sdp_solver_stats | CasADi::SDPSDQPInternal | >+------------------+-------------------------+ > >Diagrams > >C++ includes: sdp_sdqp_solver.hpp -} newtype SDPSDQPSolver = SDPSDQPSolver (ForeignPtr SDPSDQPSolver') -- typeclass decl class SDPSDQPSolverClass a where castSDPSDQPSolver :: a -> SDPSDQPSolver instance SDPSDQPSolverClass SDPSDQPSolver where castSDPSDQPSolver = id -- baseclass instances instance SharedObjectClass SDPSDQPSolver where castSharedObject (SDPSDQPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SDPSDQPSolver where castPrintableObject (SDPSDQPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SDPSDQPSolver where castOptionsFunctionality (SDPSDQPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SDPSDQPSolver where castFunction (SDPSDQPSolver x) = Function (castForeignPtr x) instance SDQPSolverClass SDPSDQPSolver where castSDQPSolver (SDPSDQPSolver x) = SDQPSolver (castForeignPtr x) instance IOInterfaceFunctionClass SDPSDQPSolver where castIOInterfaceFunction (SDPSDQPSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SDPSDQPSolver (Ptr SDPSDQPSolver') where marshal (SDPSDQPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SDPSDQPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SDPSDQPSolver" c_delete_CasADi__SDPSDQPSolver :: FunPtr (Ptr SDPSDQPSolver' -> IO ()) instance WrapReturn (Ptr SDPSDQPSolver') SDPSDQPSolver where wrapReturn = (fmap SDPSDQPSolver) . (newForeignPtr c_delete_CasADi__SDPSDQPSolver) -- raw decl data SDPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass SDPSolver where castSharedObject (SDPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SDPSolver where castPrintableObject (SDPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SDPSolver where castOptionsFunctionality (SDPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SDPSolver where castFunction (SDPSolver x) = Function (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 CasadiOptions' -- data decl {-| >[INTERNAL] 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 Slice' -- data decl {-| >[INTERNAL] 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 CustomEvaluate' -- data decl {-| >[INTERNAL] 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 SharedObjectClass CustomEvaluate where castSharedObject (CustomEvaluate x) = SharedObject (castForeignPtr x) instance PrintableObjectClass CustomEvaluate where castPrintableObject (CustomEvaluate x) = PrintableObject (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 GenMX' -- data decl {-| >[INTERNAL] Matrix base >class. > >This is a common base class for MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. The class is designed with the idea that >"everything is a matrix", that is, also scalars and vectors. This >philosophy makes it easy to use and to interface in particularily with >Python and Matlab/Octave. The syntax tries to stay as close as possible to >the ublas syntax when it comes to vector/matrix operations. Index starts >with 0. Index vec happens as follows: (rr,cc) -> k = rr+cc*size1() Vectors >are column vectors. The storage format is Compressed Column Storage (CCS), >similar to that used for sparse matrices in Matlab, but unlike this format, >we do allow for elements to be structurally non-zero but numerically zero. >The sparsity pattern, which is reference counted and cached, can be accessed >with Sparsity& sparsity() Joel Andersson > >C++ includes: generic_matrix.hpp -} newtype GenMX = GenMX (ForeignPtr GenMX') -- typeclass decl class GenMXClass a where castGenMX :: a -> GenMX instance GenMXClass GenMX where castGenMX = id -- baseclass instances -- helper instances instance Marshal GenMX (Ptr GenMX') where marshal (GenMX x) = return (unsafeForeignPtrToPtr x) marshalFree (GenMX x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericMatrix_CasADi__MX_" c_delete_CasADi__GenericMatrix_CasADi__MX_ :: FunPtr (Ptr GenMX' -> IO ()) instance WrapReturn (Ptr GenMX') GenMX where wrapReturn = (fmap GenMX) . (newForeignPtr c_delete_CasADi__GenericMatrix_CasADi__MX_) -- raw decl data ControlSimulator' -- data decl {-| >[INTERNAL] 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 continous >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 | >| | | | wether | | >| | | | 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 SharedObjectClass ControlSimulator where castSharedObject (ControlSimulator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass ControlSimulator where castPrintableObject (ControlSimulator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass ControlSimulator where castOptionsFunctionality (ControlSimulator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass ControlSimulator where castFunction (ControlSimulator x) = Function (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 IMatrix' -- data decl {-| >[INTERNAL] Sparse matrix class. SX >and DMatrix are specializations. > >General sparse matrix class that is designed with the idea that "everything >is a matrix", that is, also scalars and vectors. This philosophy makes it >easy to use and to interface in particularily with Python and Matlab/Octave. >Index starts with 0. Index vec happens as follows: (rr,cc) -> k = >rr+cc*size1() Vectors are column vectors. The storage format is Compressed >Column Storage (CCS), similar to that used for sparse matrices in Matlab, >but unlike this format, we do allow for elements to be structurally non-zero >but numerically zero. Matrix is polymorphic with a >std::vector that contain all non- identical-zero elements. The >sparsity can be accessed with Sparsity& sparsity() Joel Andersson > >C++ includes: casadi_types.hpp -} 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) instance GenIMatrixClass IMatrix where castGenIMatrix (IMatrix x) = GenIMatrix (castForeignPtr x) instance ExpIMatrixClass IMatrix where castExpIMatrix (IMatrix x) = ExpIMatrix (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__Matrix_int_" c_delete_CasADi__Matrix_int_ :: FunPtr (Ptr IMatrix' -> IO ()) instance WrapReturn (Ptr IMatrix') IMatrix where wrapReturn = (fmap IMatrix) . (newForeignPtr c_delete_CasADi__Matrix_int_) -- raw decl data SXElement' -- data decl {-| >[INTERNAL] The basic scalar >symbolic class of CasADi. > >Joel Andersson > >C++ includes: sx_element.hpp -} newtype SXElement = SXElement (ForeignPtr SXElement') -- typeclass decl class SXElementClass a where castSXElement :: a -> SXElement instance SXElementClass SXElement where castSXElement = id -- baseclass instances instance ExpSXElementClass SXElement where castExpSXElement (SXElement x) = ExpSXElement (castForeignPtr x) -- 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 SCPgen' -- data decl {-| >[INTERNAL] A structure-exploiting >sequential quadratic programming (to be come sequential convex programming) >method for nonlinear programming. > >Joel Andersson, Attila Kozma and 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) | | >+--------------+--------------+--------------+--------------+--------------+ >| beta | OT_REAL | 0.800 | Line-search | CasADi::SCPg | >| | | | parameter, | enInternal | >| | | | restoration | | >| | | | factor of | | >| | | | stepsize | | >+--------------+--------------+--------------+--------------+--------------+ >| c1 | OT_REAL | 0.000 | Armijo | CasADi::SCPg | >| | | | condition, | enInternal | >| | | | coefficient | | >| | | | of decrease | | >| | | | in merit | | >+--------------+--------------+--------------+--------------+--------------+ >| codegen | OT_BOOLEAN | false | C-code | CasADi::SCPg | >| | | | generation | enInternal | >+--------------+--------------+--------------+--------------+--------------+ >| compiler | OT_STRING | "gcc -fPIC | Compiler | CasADi::SCPg | >| | | -O2" | command to | enInternal | >| | | | be used for | | >| | | | 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| expand | OT_BOOLEAN | false | Expand the | CasADi::NLPS | >| | | | NLP function | olverInterna | >| | | | in terms of | l | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_f | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | objective | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_g | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | constraint | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| gauss_newton | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. Use | olverInterna | >| | | | Gauss Newton | l | >| | | | Hessian appr | | >| | | | oximation | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_gra | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| dient | | ) | option. | olverInterna | >| | | | Generate a | l | >| | | | function for | | >| | | | calculating | | >| | | | the gradient | | >| | | | of the | | >| | | | objective. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_hes | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| sian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Hessian of | | >| | | | the | | >| | | | Lagrangian | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_jac | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| obian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Jacobian of | | >| | | | the | | >| | | | constraints | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| hessian_appr | OT_STRING | "exact" | gauss- | CasADi::SCPg | >| oximation | | | newton|exact | enInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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. | | >+--------------+--------------+--------------+--------------+--------------+ >| lbfgs_memory | OT_INTEGER | 10 | Size of | CasADi::SCPg | >| | | | L-BFGS | enInternal | >| | | | memory. | | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter | OT_INTEGER | 50 | Maximum | CasADi::SCPg | >| | | | number of | enInternal | >| | | | SQP | | >| | | | iterations | | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter_ls | OT_INTEGER | 1 | Maximum | CasADi::SCPg | >| | | | number of | enInternal | >| | | | linesearch | | >| | | | iterations | | >+--------------+--------------+--------------+--------------+--------------+ >| merit_memsiz | OT_INTEGER | 4 | Size of | CasADi::SCPg | >| e | | | memory to | enInternal | >| | | | store | | >| | | | history of | | >| | | | merit | | >| | | | function | | >| | | | values | | >+--------------+--------------+--------------+--------------+--------------+ >| merit_start | OT_REAL | 0.000 | Lower bound | CasADi::SCPg | >| | | | for the | enInternal | >| | | | merit | | >| | | | function | | >| | | | parameter | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::SCPg | >| | | | uts) (eval_ | enInternal | >| | | | f|eval_g|eva | | >| | | | l_jac_g|eval | | >| | | | _grad_f|eval | | >| | | | _h|qp|dx) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | CasADi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| name_x | OT_STRINGVEC | GenericType( | Names of the | CasADi::SCPg | >| | TOR | ) | variables. | enInternal | >+--------------+--------------+--------------+--------------+--------------+ >| parametric | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. | olverInterna | >| | | | Expect F, G, | l | >| | | | H, J to have | | >| | | | an | | >| | | | additional | | >| | | | input | | >| | | | argument | | >| | | | appended at | | >| | | | the end, | | >| | | | denoting | | >| | | | fixed | | >| | | | parameters. | | >+--------------+--------------+--------------+--------------+--------------+ >| print_header | OT_BOOLEAN | true | Print the | CasADi::SCPg | >| | | | header with | enInternal | >| | | | problem | | >| | | | statistics | | >+--------------+--------------+--------------+--------------+--------------+ >| print_time | OT_BOOLEAN | true | Print | CasADi::SCPg | >| | | | information | enInternal | >| | | | about | | >| | | | execution | | >| | | | time | | >+--------------+--------------+--------------+--------------+--------------+ >| print_x | OT_INTEGERVE | GenericType( | Which | CasADi::SCPg | >| | CTOR | ) | variables to | enInternal | >| | | | print. | | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver | OT_QPSOLVER | GenericType( | The QP | CasADi::SCPg | >| | | ) | solver to be | enInternal | >| | | | used by the | | >| | | | SQP method | | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver_op | OT_DICTIONAR | GenericType( | Options to | CasADi::SCPg | >| tions | Y | ) | be passed to | enInternal | >| | | | the QP | | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| reg_threshol | OT_REAL | 0.000 | Threshold | CasADi::SCPg | >| d | | | for the regu | enInternal | >| | | | larization. | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| regularize | OT_BOOLEAN | false | Automatic re | CasADi::SCPg | >| | | | gularization | enInternal | >| | | | of Lagrange | | >| | | | Hessian. | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_du | OT_REAL | 0.000 | Stopping | CasADi::SCPg | >| | | | criterion | enInternal | >| | | | for dual inf | | >| | | | easability | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_pr | OT_REAL | 0.000 | Stopping | CasADi::SCPg | >| | | | criterion | enInternal | >| | | | for primal i | | >| | | | nfeasibility | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_pr_step | OT_REAL | 0.000 | Stopping | CasADi::SCPg | >| | | | criterion | enInternal | >| | | | for the step | | >| | | | size | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_reg | OT_REAL | 0.000 | Stopping | CasADi::SCPg | >| | | | criterion | enInternal | >| | | | for regulari | | >| | | | zation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | CasADi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | CasADi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ >| warn_initial | OT_BOOLEAN | false | Warn if the | CasADi::NLPS | >| _bounds | | | initial | olverInterna | >| | | | guess does | l | >| | | | not satisfy | | >| | | | LBX and UBX | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available monitors >+-------------+--------------------------+ >| Id | Used in | >+=============+==========================+ >| dx | CasADi::SCPgenInternal | >+-------------+--------------------------+ >| eval_f | CasADi::SCPgenInternal | >+-------------+--------------------------+ >| eval_g | CasADi::SCPgenInternal | >+-------------+--------------------------+ >| eval_grad_f | CasADi::SCPgenInternal | >+-------------+--------------------------+ >| eval_h | CasADi::SCPgenInternal | >+-------------+--------------------------+ >| eval_jac_g | CasADi::SCPgenInternal | >+-------------+--------------------------+ >| inputs | CasADi::FunctionInternal | >+-------------+--------------------------+ >| outputs | CasADi::FunctionInternal | >+-------------+--------------------------+ >| qp | CasADi::SCPgenInternal | >+-------------+--------------------------+ > >>List of available stats >+------------+------------------------+ >| Id | Used in | >+============+========================+ >| iter_count | CasADi::SCPgenInternal | >+------------+------------------------+ > >Diagrams > >C++ includes: scpgen.hpp -} newtype SCPgen = SCPgen (ForeignPtr SCPgen') -- typeclass decl class SCPgenClass a where castSCPgen :: a -> SCPgen instance SCPgenClass SCPgen where castSCPgen = id -- baseclass instances instance SharedObjectClass SCPgen where castSharedObject (SCPgen x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SCPgen where castPrintableObject (SCPgen x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SCPgen where castOptionsFunctionality (SCPgen x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SCPgen where castFunction (SCPgen x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass SCPgen where castIOInterfaceFunction (SCPgen x) = IOInterfaceFunction (castForeignPtr x) instance NLPSolverClass SCPgen where castNLPSolver (SCPgen x) = NLPSolver (castForeignPtr x) -- helper instances instance Marshal SCPgen (Ptr SCPgen') where marshal (SCPgen x) = return (unsafeForeignPtrToPtr x) marshalFree (SCPgen x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SCPgen" c_delete_CasADi__SCPgen :: FunPtr (Ptr SCPgen' -> IO ()) instance WrapReturn (Ptr SCPgen') SCPgen where wrapReturn = (fmap SCPgen) . (newForeignPtr c_delete_CasADi__SCPgen) -- raw decl data NLPImplicitSolver' -- data decl {-| >[INTERNAL] Use an >NLPSolver as ImplicitFunction solver. > >The equation: > >F(z, x1, x2, ..., xn) == 0 > >where d_F/dz is invertable, 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. > >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) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >| | | | wether | | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver | OT_NLPSOLVER | GenericType( | The | CasADi::NLPI | >| | | ) | NLPSolver | mplicitInter | >| | | | used to | nal | >| | | | solve the | | >| | | | implicit | | >| | | | system. | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::NLPI | >| ptions | Y | ) | be passed to | mplicitInter | >| | | | the | nal | >| | | | NLPSolver | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+==================+=============================+ >| nlp_solver_stats | CasADi::NLPImplicitInternal | >+------------------+-----------------------------+ > >Diagrams > >C++ includes: nlp_implicit_solver.hpp -} newtype NLPImplicitSolver = NLPImplicitSolver (ForeignPtr NLPImplicitSolver') -- typeclass decl class NLPImplicitSolverClass a where castNLPImplicitSolver :: a -> NLPImplicitSolver instance NLPImplicitSolverClass NLPImplicitSolver where castNLPImplicitSolver = id -- baseclass instances instance SharedObjectClass NLPImplicitSolver where castSharedObject (NLPImplicitSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass NLPImplicitSolver where castPrintableObject (NLPImplicitSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass NLPImplicitSolver where castOptionsFunctionality (NLPImplicitSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass NLPImplicitSolver where castFunction (NLPImplicitSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass NLPImplicitSolver where castIOInterfaceFunction (NLPImplicitSolver x) = IOInterfaceFunction (castForeignPtr x) instance ImplicitFunctionClass NLPImplicitSolver where castImplicitFunction (NLPImplicitSolver x) = ImplicitFunction (castForeignPtr x) -- helper instances instance Marshal NLPImplicitSolver (Ptr NLPImplicitSolver') where marshal (NLPImplicitSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (NLPImplicitSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__NLPImplicitSolver" c_delete_CasADi__NLPImplicitSolver :: FunPtr (Ptr NLPImplicitSolver' -> IO ()) instance WrapReturn (Ptr NLPImplicitSolver') NLPImplicitSolver where wrapReturn = (fmap NLPImplicitSolver) . (newForeignPtr c_delete_CasADi__NLPImplicitSolver) -- raw decl data ExternalFunction' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass ExternalFunction where castSharedObject (ExternalFunction x) = SharedObject (castForeignPtr x) instance PrintableObjectClass ExternalFunction where castPrintableObject (ExternalFunction x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass ExternalFunction where castOptionsFunctionality (ExternalFunction x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass ExternalFunction where castFunction (ExternalFunction x) = Function (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 SimpleIndefDpleSolver' -- data decl {-| >[INTERNAL] Solving >the Discrete Periodic Lyapunov Equations with regular Linear Solvers. > >Given matrices A_k and symmetric V_k, k = 0..K-1 > >A_k in R^(n x n) V_k in R^n > >provides all of P_k that satisfy: > >P_0 = A_(K-1)*P_(K-1)*A_(K-1)' + V_k P_k+1 = A_k*P_k*A_k' + V_k for k = >1..K-1 > >Uses Periodic Schur Decomposition (simple) and does not assume positive >definiteness. Based on Periodic Lyapunov equations: some applications and >new algorithms. Int. J. Control, vol. 67, pp. 69-87, 1997. > >Joris gillis > >>Input scheme: CasADi::DPLEInput (DPLE_NUM_IN = 3) [dpleIn] >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| DPLE_A | a | A matrices (horzcat | >| | | when const_dim, | >| | | blkdiag otherwise) . | >+------------------------+------------------------+------------------------+ >| DPLE_V | v | V matrices (horzcat | >| | | when const_dim, | >| | | blkdiag otherwise) . | >+------------------------+------------------------+------------------------+ > >>Output scheme: CasADi::DPLEOutput (DPLE_NUM_OUT = 2) [dpleOut] >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| DPLE_P | p | Lyapunov matrix | >| | | (horzcat when | >| | | const_dim, blkdiag | >| | | otherwise) (cholesky | >| | | of P if pos_def) . | >+------------------------+------------------------+------------------------+ > >>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) | | >+--------------+--------------+--------------+--------------+--------------+ >| const_dim | OT_BOOLEAN | true | Assume | CasADi::Dple | >| | | | constant | Internal | >| | | | dimension of | | >| | | | P | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| eps_unstable | OT_REAL | 0.000 | A margin for | CasADi::Dple | >| | | | unstability | Internal | >| | | | detection | | >+--------------+--------------+--------------+--------------+--------------+ >| error_unstab | OT_BOOLEAN | false | Throw an | CasADi::Dple | >| le | | | exception | Internal | >| | | | when it is | | >| | | | detected | | >| | | | that Product | | >| | | | (A_i,i=N..1) | | >| | | | has | | >| | | | eigenvalues | | >| | | | greater than | | >| | | | 1-eps_unstab | | >| | | | le | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_LINEARSOL | GenericType( | User-defined | CasADi::Simp | >| r | VER | ) | linear | leIndefDpleI | >| | | | solver | nternal | >| | | | class. | | >| | | | Needed for s | | >| | | | ensitivities | | >| | | | . | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | CasADi::Simp | >| r_options | Y | ) | be passed to | leIndefDpleI | >| | | | the linear | nternal | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| pos_def | OT_BOOLEAN | false | Assume P | CasADi::Dple | >| | | | positive | Internal | >| | | | definite | | >+--------------+--------------+--------------+--------------+--------------+ >| 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: simple_indef_dple_solver.hpp -} newtype SimpleIndefDpleSolver = SimpleIndefDpleSolver (ForeignPtr SimpleIndefDpleSolver') -- typeclass decl class SimpleIndefDpleSolverClass a where castSimpleIndefDpleSolver :: a -> SimpleIndefDpleSolver instance SimpleIndefDpleSolverClass SimpleIndefDpleSolver where castSimpleIndefDpleSolver = id -- baseclass instances instance SharedObjectClass SimpleIndefDpleSolver where castSharedObject (SimpleIndefDpleSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SimpleIndefDpleSolver where castPrintableObject (SimpleIndefDpleSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SimpleIndefDpleSolver where castOptionsFunctionality (SimpleIndefDpleSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SimpleIndefDpleSolver where castFunction (SimpleIndefDpleSolver x) = Function (castForeignPtr x) instance DpleSolverClass SimpleIndefDpleSolver where castDpleSolver (SimpleIndefDpleSolver x) = DpleSolver (castForeignPtr x) instance IOInterfaceFunctionClass SimpleIndefDpleSolver where castIOInterfaceFunction (SimpleIndefDpleSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SimpleIndefDpleSolver (Ptr SimpleIndefDpleSolver') where marshal (SimpleIndefDpleSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SimpleIndefDpleSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SimpleIndefDpleSolver" c_delete_CasADi__SimpleIndefDpleSolver :: FunPtr (Ptr SimpleIndefDpleSolver' -> IO ()) instance WrapReturn (Ptr SimpleIndefDpleSolver') SimpleIndefDpleSolver where wrapReturn = (fmap SimpleIndefDpleSolver) . (newForeignPtr c_delete_CasADi__SimpleIndefDpleSolver) -- raw decl data DirectCollocation' -- data decl {-| >[INTERNAL] Direct >collocation. > >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) | | >+--------------+--------------+--------------+--------------+--------------+ >| collocation_ | OT_STRING | "radau" | Collocation | CasADi::Dire | >| scheme | | | scheme (rada | ctCollocatio | >| | | | u|legendre) | nInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >| | | | wether | | >| | | | 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| interpolatio | OT_INTEGER | 3 | Order of the | CasADi::Dire | >| n_order | | | interpolatin | ctCollocatio | >| | | | g | nInternal | >| | | | polynomials | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver | OT_NLPSOLVER | GenericType( | An NLPSolver | CasADi::Dire | >| | | ) | creator | ctCollocatio | >| | | | function | nInternal | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::Dire | >| ptions | Y | ) | be passed to | ctCollocatio | >| | | | the NLP | nInternal | >| | | | Solver | | >+--------------+--------------+--------------+--------------+--------------+ >| 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: direct_collocation.hpp -} newtype DirectCollocation = DirectCollocation (ForeignPtr DirectCollocation') -- typeclass decl class DirectCollocationClass a where castDirectCollocation :: a -> DirectCollocation instance DirectCollocationClass DirectCollocation where castDirectCollocation = id -- baseclass instances instance SharedObjectClass DirectCollocation where castSharedObject (DirectCollocation x) = SharedObject (castForeignPtr x) instance PrintableObjectClass DirectCollocation where castPrintableObject (DirectCollocation x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass DirectCollocation where castOptionsFunctionality (DirectCollocation x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass DirectCollocation where castFunction (DirectCollocation x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass DirectCollocation where castIOInterfaceFunction (DirectCollocation x) = IOInterfaceFunction (castForeignPtr x) instance OCPSolverClass DirectCollocation where castOCPSolver (DirectCollocation x) = OCPSolver (castForeignPtr x) -- helper instances instance Marshal DirectCollocation (Ptr DirectCollocation') where marshal (DirectCollocation x) = return (unsafeForeignPtrToPtr x) marshalFree (DirectCollocation x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__DirectCollocation" c_delete_CasADi__DirectCollocation :: FunPtr (Ptr DirectCollocation' -> IO ()) instance WrapReturn (Ptr DirectCollocation') DirectCollocation where wrapReturn = (fmap DirectCollocation) . (newForeignPtr c_delete_CasADi__DirectCollocation) -- raw decl data QPStabilizer' -- data decl {-| >[INTERNAL] IPOPT QP Solver for >quadratic programming. > >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. > >Joris Gillis > >>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 | >| | | | wether | | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver | OT_QPSOLVER | GenericType( | The QP | CasADi::QPSt | >| | | ) | solver used | abilizerInte | >| | | | to solve the | rnal | >| | | | stabilized | | >| | | | QPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| qp_solver_op | OT_DICTIONAR | GenericType( | Options to | CasADi::QPSt | >| tions | Y | ) | be passed to | abilizerInte | >| | | | the QP | rnal | >| | | | solver | | >| | | | instance | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+=================+==============================+ >| qp_solver_stats | CasADi::QPStabilizerInternal | >+-----------------+------------------------------+ > >Diagrams > >C++ includes: qp_stabilizer.hpp -} newtype QPStabilizer = QPStabilizer (ForeignPtr QPStabilizer') -- typeclass decl class QPStabilizerClass a where castQPStabilizer :: a -> QPStabilizer instance QPStabilizerClass QPStabilizer where castQPStabilizer = id -- baseclass instances instance SharedObjectClass QPStabilizer where castSharedObject (QPStabilizer x) = SharedObject (castForeignPtr x) instance StabilizedQPSolverClass QPStabilizer where castStabilizedQPSolver (QPStabilizer x) = StabilizedQPSolver (castForeignPtr x) instance PrintableObjectClass QPStabilizer where castPrintableObject (QPStabilizer x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass QPStabilizer where castOptionsFunctionality (QPStabilizer x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass QPStabilizer where castFunction (QPStabilizer x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass QPStabilizer where castIOInterfaceFunction (QPStabilizer x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal QPStabilizer (Ptr QPStabilizer') where marshal (QPStabilizer x) = return (unsafeForeignPtrToPtr x) marshalFree (QPStabilizer x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__QPStabilizer" c_delete_CasADi__QPStabilizer :: FunPtr (Ptr QPStabilizer' -> IO ()) instance WrapReturn (Ptr QPStabilizer') QPStabilizer where wrapReturn = (fmap QPStabilizer) . (newForeignPtr c_delete_CasADi__QPStabilizer) -- raw decl data GenIMatrix' -- data decl {-| >[INTERNAL] Matrix base >class. > >This is a common base class for MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. The class is designed with the idea that >"everything is a matrix", that is, also scalars and vectors. This >philosophy makes it easy to use and to interface in particularily with >Python and Matlab/Octave. The syntax tries to stay as close as possible to >the ublas syntax when it comes to vector/matrix operations. Index starts >with 0. Index vec happens as follows: (rr,cc) -> k = rr+cc*size1() Vectors >are column vectors. The storage format is Compressed Column Storage (CCS), >similar to that used for sparse matrices in Matlab, but unlike this format, >we do allow for elements to be structurally non-zero but numerically zero. >The sparsity pattern, which is reference counted and cached, can be accessed >with Sparsity& sparsity() Joel Andersson > >C++ includes: generic_matrix.hpp -} newtype GenIMatrix = GenIMatrix (ForeignPtr GenIMatrix') -- typeclass decl class GenIMatrixClass a where castGenIMatrix :: a -> GenIMatrix instance GenIMatrixClass GenIMatrix where castGenIMatrix = id -- baseclass instances -- helper instances instance Marshal GenIMatrix (Ptr GenIMatrix') where marshal (GenIMatrix x) = return (unsafeForeignPtrToPtr x) marshalFree (GenIMatrix x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericMatrix_CasADi__Matrix_int__" c_delete_CasADi__GenericMatrix_CasADi__Matrix_int__ :: FunPtr (Ptr GenIMatrix' -> IO ()) instance WrapReturn (Ptr GenIMatrix') GenIMatrix where wrapReturn = (fmap GenIMatrix) . (newForeignPtr c_delete_CasADi__GenericMatrix_CasADi__Matrix_int__) -- raw decl data Callback' -- data decl {-| >[INTERNAL] 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 SharedObjectClass Callback where castSharedObject (Callback x) = SharedObject (castForeignPtr x) instance PrintableObjectClass Callback where castPrintableObject (Callback x) = PrintableObject (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 SOCPQCQPSolver' -- data decl {-| >[INTERNAL] SOCP QCQP Solver >for quadratic programming. > >Note: this implementation relies on Cholesky decomposition: Chol(H) = L -> H >= LL' with L lower triangular This requires Pi, H to be positive definite. >Positive semi-definite is not sufficient. Notably, H==0 will not work. > >A better implementation would rely on matrix square root, but we need >singular value decomposition to implement that. > >This implementation makes use of the epigraph reformulation: min f(x) x > >min t x,t f(x) <= t > >This implementation makes use of the following identity: > >|| Gx+h||_2 <= e'x + f > >x'(G'G - ee')x + (2 h'G - 2 f e') x + h'h - f <= 0 > >where we put e = [0 0 ... 1] for the qadratic constraint arising from the >epigraph reformulation and e==0 for all other qc. > >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 | >| | | | wether | | >| | | | 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| socp_solver | OT_SOCPSOLVE | GenericType( | The | CasADi::SOCP | >| | R | ) | SOCPSolver | QCQPInternal | >| | | | used to | | >| | | | solve the | | >| | | | QCQPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| socp_solver_ | OT_DICTIONAR | GenericType( | Options to | CasADi::SOCP | >| options | Y | ) | be passed to | QCQPInternal | >| | | | the | | >| | | | SOCPSOlver | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+===================+==========================+ >| socp_solver_stats | CasADi::SOCPQCQPInternal | >+-------------------+--------------------------+ > >Diagrams > >C++ includes: socp_qcqp_solver.hpp -} newtype SOCPQCQPSolver = SOCPQCQPSolver (ForeignPtr SOCPQCQPSolver') -- typeclass decl class SOCPQCQPSolverClass a where castSOCPQCQPSolver :: a -> SOCPQCQPSolver instance SOCPQCQPSolverClass SOCPQCQPSolver where castSOCPQCQPSolver = id -- baseclass instances instance SharedObjectClass SOCPQCQPSolver where castSharedObject (SOCPQCQPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SOCPQCQPSolver where castPrintableObject (SOCPQCQPSolver x) = PrintableObject (castForeignPtr x) instance QCQPSolverClass SOCPQCQPSolver where castQCQPSolver (SOCPQCQPSolver x) = QCQPSolver (castForeignPtr x) instance OptionsFunctionalityClass SOCPQCQPSolver where castOptionsFunctionality (SOCPQCQPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SOCPQCQPSolver where castFunction (SOCPQCQPSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass SOCPQCQPSolver where castIOInterfaceFunction (SOCPQCQPSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SOCPQCQPSolver (Ptr SOCPQCQPSolver') where marshal (SOCPQCQPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SOCPQCQPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SOCPQCQPSolver" c_delete_CasADi__SOCPQCQPSolver :: FunPtr (Ptr SOCPQCQPSolver' -> IO ()) instance WrapReturn (Ptr SOCPQCQPSolver') SOCPQCQPSolver where wrapReturn = (fmap SOCPQCQPSolver) . (newForeignPtr c_delete_CasADi__SOCPQCQPSolver) -- raw decl data QCQPQPSolver' -- data decl {-| >[INTERNAL] Use a QCQP solver >to solve q QP. > >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. > >Joris Gillis > >>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 | >| | | | wether | | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| qcqp_solver | OT_QCQPSOLVE | GenericType( | The | CasADi::QCQP | >| | R | ) | QCQPSolver | QPInternal | >| | | | used to | | >| | | | solve the | | >| | | | QPs. | | >+--------------+--------------+--------------+--------------+--------------+ >| qcqp_solver_ | OT_DICTIONAR | GenericType( | Options to | CasADi::QCQP | >| options | Y | ) | be passed to | QPInternal | >| | | | the | | >| | | | QCQPSOlver | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+===================+========================+ >| qcqp_solver_stats | CasADi::QCQPQPInternal | >+-------------------+------------------------+ > >Diagrams > >C++ includes: qcqp_qp_solver.hpp -} newtype QCQPQPSolver = QCQPQPSolver (ForeignPtr QCQPQPSolver') -- typeclass decl class QCQPQPSolverClass a where castQCQPQPSolver :: a -> QCQPQPSolver instance QCQPQPSolverClass QCQPQPSolver where castQCQPQPSolver = id -- baseclass instances instance SharedObjectClass QCQPQPSolver where castSharedObject (QCQPQPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass QCQPQPSolver where castPrintableObject (QCQPQPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass QCQPQPSolver where castOptionsFunctionality (QCQPQPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass QCQPQPSolver where castFunction (QCQPQPSolver x) = Function (castForeignPtr x) instance QPSolverClass QCQPQPSolver where castQPSolver (QCQPQPSolver x) = QPSolver (castForeignPtr x) instance IOInterfaceFunctionClass QCQPQPSolver where castIOInterfaceFunction (QCQPQPSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal QCQPQPSolver (Ptr QCQPQPSolver') where marshal (QCQPQPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (QCQPQPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__QCQPQPSolver" c_delete_CasADi__QCQPQPSolver :: FunPtr (Ptr QCQPQPSolver' -> IO ()) instance WrapReturn (Ptr QCQPQPSolver') QCQPQPSolver where wrapReturn = (fmap QCQPQPSolver) . (newForeignPtr c_delete_CasADi__QCQPQPSolver) -- raw decl data ExpSX' -- data decl {-| >[INTERNAL] Expression >interface. > >This is a common base class for SX, MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. Joel Andersson > >C++ includes: generic_expression.hpp -} newtype ExpSX = ExpSX (ForeignPtr ExpSX') -- typeclass decl class ExpSXClass a where castExpSX :: a -> ExpSX instance ExpSXClass ExpSX where castExpSX = id -- baseclass instances -- helper instances instance Marshal ExpSX (Ptr ExpSX') where marshal (ExpSX x) = return (unsafeForeignPtrToPtr x) marshalFree (ExpSX x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericExpression_CasADi__Matrix_CasADi__SXElement__" c_delete_CasADi__GenericExpression_CasADi__Matrix_CasADi__SXElement__ :: FunPtr (Ptr ExpSX' -> IO ()) instance WrapReturn (Ptr ExpSX') ExpSX where wrapReturn = (fmap ExpSX) . (newForeignPtr c_delete_CasADi__GenericExpression_CasADi__Matrix_CasADi__SXElement__) -- raw decl data Integrator' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass Integrator where castSharedObject (Integrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass Integrator where castPrintableObject (Integrator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass Integrator where castOptionsFunctionality (Integrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass Integrator where castFunction (Integrator x) = Function (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 WeakRef' -- data decl {-| >[INTERNAL] Weak reference type A >weak reference to a SharedObject. > >Joel Andersson > >C++ includes: weak_ref.hpp -} newtype WeakRef = WeakRef (ForeignPtr WeakRef') -- typeclass decl class WeakRefClass a where castWeakRef :: a -> WeakRef instance WeakRefClass WeakRef where castWeakRef = id -- baseclass instances instance SharedObjectClass WeakRef where castSharedObject (WeakRef x) = SharedObject (castForeignPtr x) instance PrintableObjectClass WeakRef where castPrintableObject (WeakRef x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal WeakRef (Ptr WeakRef') where marshal (WeakRef x) = return (unsafeForeignPtrToPtr x) marshalFree (WeakRef x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__WeakRef" c_delete_CasADi__WeakRef :: FunPtr (Ptr WeakRef' -> IO ()) instance WrapReturn (Ptr WeakRef') WeakRef where wrapReturn = (fmap WeakRef) . (newForeignPtr c_delete_CasADi__WeakRef) -- raw decl data Simulator' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass Simulator where castSharedObject (Simulator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass Simulator where castPrintableObject (Simulator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass Simulator where castOptionsFunctionality (Simulator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass Simulator where castFunction (Simulator x) = Function (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 Parallelizer' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass Parallelizer where castSharedObject (Parallelizer x) = SharedObject (castForeignPtr x) instance PrintableObjectClass Parallelizer where castPrintableObject (Parallelizer x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass Parallelizer where castOptionsFunctionality (Parallelizer x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass Parallelizer where castFunction (Parallelizer x) = Function (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 SimpleHomotopyNLPSolver' -- data decl {-| >[INTERNAL] Solving >an NLP homotopy with regular NLP solvers. > >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 | >| | | | wether | | >| | | | 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 | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver | OT_NLPSOLVER | GenericType( | The NLP | CasADi::Simp | >| | | ) | solver to be | leHomotopyNL | >| | | | used by the | PInternal | >| | | | Homotopy | | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::Simp | >| ptions | Y | ) | be passed to | leHomotopyNL | >| | | | the Homotopy | PInternal | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| num_steps | OT_INTEGER | 10 | Take this | CasADi::Simp | >| | | | many steps | leHomotopyNL | >| | | | to go from | PInternal | >| | | | tau=0 to | | >| | | | tau=1. | | >+--------------+--------------+--------------+--------------+--------------+ >| 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: simple_homotopy_nlp_solver.hpp -} newtype SimpleHomotopyNLPSolver = SimpleHomotopyNLPSolver (ForeignPtr SimpleHomotopyNLPSolver') -- typeclass decl class SimpleHomotopyNLPSolverClass a where castSimpleHomotopyNLPSolver :: a -> SimpleHomotopyNLPSolver instance SimpleHomotopyNLPSolverClass SimpleHomotopyNLPSolver where castSimpleHomotopyNLPSolver = id -- baseclass instances instance HomotopyNLPSolverClass SimpleHomotopyNLPSolver where castHomotopyNLPSolver (SimpleHomotopyNLPSolver x) = HomotopyNLPSolver (castForeignPtr x) instance SharedObjectClass SimpleHomotopyNLPSolver where castSharedObject (SimpleHomotopyNLPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SimpleHomotopyNLPSolver where castPrintableObject (SimpleHomotopyNLPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SimpleHomotopyNLPSolver where castOptionsFunctionality (SimpleHomotopyNLPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SimpleHomotopyNLPSolver where castFunction (SimpleHomotopyNLPSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass SimpleHomotopyNLPSolver where castIOInterfaceFunction (SimpleHomotopyNLPSolver x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SimpleHomotopyNLPSolver (Ptr SimpleHomotopyNLPSolver') where marshal (SimpleHomotopyNLPSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SimpleHomotopyNLPSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SimpleHomotopyNLPSolver" c_delete_CasADi__SimpleHomotopyNLPSolver :: FunPtr (Ptr SimpleHomotopyNLPSolver' -> IO ()) instance WrapReturn (Ptr SimpleHomotopyNLPSolver') SimpleHomotopyNLPSolver where wrapReturn = (fmap SimpleHomotopyNLPSolver) . (newForeignPtr c_delete_CasADi__SimpleHomotopyNLPSolver) -- raw decl data SundialsIntegrator' -- data decl {-| >[INTERNAL] Interface to >the Sundials integrators. > >Base class for integrators. 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. > >>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 | >+==============+==============+==============+==============+==============+ >| abstol | OT_REAL | 0.000 | Absolute | CasADi::Sund | >| | | | tolerence | ialsInternal | >| | | | for the IVP | | >| | | | solution | | >+--------------+--------------+--------------+--------------+--------------+ >| abstolB | OT_REAL | GenericType( | Absolute | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | adjoint | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | abstol] | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| exact_jacobi | OT_BOOLEAN | true | Use exact | CasADi::Sund | >| an | | | Jacobian | ialsInternal | >| | | | information | | >| | | | for the | | >| | | | forward | | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| exact_jacobi | OT_BOOLEAN | GenericType( | Use exact | CasADi::Sund | >| anB | | ) | Jacobian | ialsInternal | >| | | | information | | >| | | | for the | | >| | | | backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to exa | | >| | | | ct_jacobian] | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_augme | OT_BOOLEAN | true | If DAE | CasADi::Inte | >| nted | | | callback | gratorIntern | >| | | | functions | al | >| | | | are | | >| | | | SXFunction , | | >| | | | have | | >| | | | augmented | | >| | | | DAE callback | | >| | | | function | | >| | | | also be | | >| | | | SXFunction . | | >+--------------+--------------+--------------+--------------+--------------+ >| finite_diffe | OT_BOOLEAN | false | Use finite | CasADi::Sund | >| rence_fsens | | | differences | ialsInternal | >| | | | to | | >| | | | approximate | | >| | | | the forward | | >| | | | sensitivity | | >| | | | equations | | >| | | | (if AD is | | >| | | | not | | >| | | | available) | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_abstol | OT_REAL | GenericType( | Absolute | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | forward | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | abstol] | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_err_co | OT_BOOLEAN | true | include the | CasADi::Sund | >| n | | | forward sens | ialsInternal | >| | | | itivities in | | >| | | | all error | | >| | | | controls | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_reltol | OT_REAL | GenericType( | Relative | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | forward | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | reltol] | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_scalin | OT_REALVECTO | GenericType( | Scaling | CasADi::Sund | >| g_factors | R | ) | factor for | ialsInternal | >| | | | the | | >| | | | components | | >| | | | if finite | | >| | | | differences | | >| | | | is used | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_sensit | OT_INTEGERVE | GenericType( | Specifies | CasADi::Sund | >| iviy_paramet | CTOR | ) | which | ialsInternal | >| ers | | | components | | >| | | | will be used | | >| | | | when | | >| | | | estimating | | >| | | | the | | >| | | | sensitivity | | >| | | | equations | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| interpolatio | OT_STRING | "hermite" | Type of inte | CasADi::Sund | >| n_type | | | rpolation | ialsInternal | >| | | | for the | | >| | | | adjoint sens | | >| | | | itivities (h | | >| | | | ermite|polyn | | >| | | | omial) | | >+--------------+--------------+--------------+--------------+--------------+ >| iterative_so | OT_STRING | "gmres" | (gmres|bcgst | CasADi::Sund | >| lver | | | ab|tfqmr) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| iterative_so | OT_STRING | GenericType( | (gmres|bcgst | CasADi::Sund | >| lverB | | ) | ab|tfqmr) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_LINEARSOL | GenericType( | A custom | CasADi::Sund | >| r | VER | ) | linear | ialsInternal | >| | | | solver | | >| | | | creator | | >| | | | function | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_LINEARSOL | GenericType( | A custom | CasADi::Sund | >| rB | VER | ) | linear | ialsInternal | >| | | | solver | | >| | | | creator | | >| | | | function for | | >| | | | backwards | | >| | | | integration | | >| | | | [default: | | >| | | | equal to lin | | >| | | | ear_solver] | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | CasADi::Sund | >| r_options | Y | ) | be passed to | ialsInternal | >| | | | the linear | | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | CasADi::Sund | >| r_optionsB | Y | ) | be passed to | ialsInternal | >| | | | the linear | | >| | | | solver for | | >| | | | backwards | | >| | | | integration | | >| | | | [default: | | >| | | | equal to lin | | >| | | | ear_solver_o | | >| | | | ptions] | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | "dense" | (user_define | CasADi::Sund | >| r_type | | | d|dense|band | ialsInternal | >| | | | ed|iterative | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | GenericType( | (user_define | CasADi::Sund | >| r_typeB | | ) | d|dense|band | ialsInternal | >| | | | ed|iterative | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| lower_bandwi | OT_INTEGER | GenericType( | Lower band- | CasADi::Sund | >| dth | | ) | width of | ialsInternal | >| | | | banded | | >| | | | Jacobian (es | | >| | | | timations) | | >+--------------+--------------+--------------+--------------+--------------+ >| lower_bandwi | OT_INTEGER | GenericType( | lower band- | CasADi::Sund | >| dthB | | ) | width of | ialsInternal | >| | | | banded | | >| | | | jacobians | | >| | | | for backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to low | | >| | | | er_bandwidth | | >| | | | ] | | >+--------------+--------------+--------------+--------------+--------------+ >| max_krylov | OT_INTEGER | 10 | Maximum | CasADi::Sund | >| | | | Krylov | ialsInternal | >| | | | subspace | | >| | | | size | | >+--------------+--------------+--------------+--------------+--------------+ >| max_krylovB | OT_INTEGER | GenericType( | Maximum | CasADi::Sund | >| | | ) | krylov | ialsInternal | >| | | | subspace | | >| | | | size | | >+--------------+--------------+--------------+--------------+--------------+ >| max_multiste | OT_INTEGER | 5 | | CasADi::Sund | >| p_order | | | | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| max_num_step | OT_INTEGER | 10000 | Maximum | CasADi::Sund | >| s | | | number of | ialsInternal | >| | | | integrator | | >| | | | steps | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| pretype | OT_STRING | "none" | (none|left|r | CasADi::Sund | >| | | | ight|both) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| pretypeB | OT_STRING | GenericType( | (none|left|r | CasADi::Sund | >| | | ) | ight|both) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| print_stats | OT_BOOLEAN | false | Print out | CasADi::Inte | >| | | | statistics | gratorIntern | >| | | | after | al | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| quad_err_con | OT_BOOLEAN | false | Should the | CasADi::Sund | >| | | | quadratures | ialsInternal | >| | | | affect the | | >| | | | step size | | >| | | | control | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| reltol | OT_REAL | 0.000 | Relative | CasADi::Sund | >| | | | tolerence | ialsInternal | >| | | | for the IVP | | >| | | | solution | | >+--------------+--------------+--------------+--------------+--------------+ >| reltolB | OT_REAL | GenericType( | Relative | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | adjoint | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | reltol] | | >+--------------+--------------+--------------+--------------+--------------+ >| sensitivity_ | OT_STRING | "simultaneou | (simultaneou | CasADi::Sund | >| method | | s" | s|staggered) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| steps_per_ch | OT_INTEGER | 20 | Number of | CasADi::Sund | >| eckpoint | | | steps | ialsInternal | >| | | | between two | | >| | | | consecutive | | >| | | | checkpoints | | >+--------------+--------------+--------------+--------------+--------------+ >| stop_at_end | OT_BOOLEAN | true | Stop the | CasADi::Sund | >| | | | integrator | ialsInternal | >| | | | at the end | | >| | | | of the | | >| | | | interval | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| upper_bandwi | OT_INTEGER | GenericType( | Upper band- | CasADi::Sund | >| dth | | ) | width of | ialsInternal | >| | | | banded | | >| | | | Jacobian (es | | >| | | | timations) | | >+--------------+--------------+--------------+--------------+--------------+ >| upper_bandwi | OT_INTEGER | GenericType( | Upper band- | CasADi::Sund | >| dthB | | ) | width of | ialsInternal | >| | | | banded | | >| | | | jacobians | | >| | | | for backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to upp | | >| | | | er_bandwidth | | >| | | | ] | | >+--------------+--------------+--------------+--------------+--------------+ >| use_precondi | OT_BOOLEAN | false | Precondition | CasADi::Sund | >| tioner | | | an iterative | ialsInternal | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| use_precondi | OT_BOOLEAN | GenericType( | Precondition | CasADi::Sund | >| tionerB | | ) | an iterative | ialsInternal | >| | | | solver for | | >| | | | the | | >| | | | backwards | | >| | | | problem | | >| | | | [default: | | >| | | | equal to use | | >| | | | _preconditio | | >| | | | ner] | | >+--------------+--------------+--------------+--------------+--------------+ >| 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: sundials_integrator.hpp -} newtype SundialsIntegrator = SundialsIntegrator (ForeignPtr SundialsIntegrator') -- typeclass decl class SundialsIntegratorClass a where castSundialsIntegrator :: a -> SundialsIntegrator instance SundialsIntegratorClass SundialsIntegrator where castSundialsIntegrator = id -- baseclass instances instance SharedObjectClass SundialsIntegrator where castSharedObject (SundialsIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SundialsIntegrator where castPrintableObject (SundialsIntegrator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SundialsIntegrator where castOptionsFunctionality (SundialsIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SundialsIntegrator where castFunction (SundialsIntegrator x) = Function (castForeignPtr x) instance IntegratorClass SundialsIntegrator where castIntegrator (SundialsIntegrator x) = Integrator (castForeignPtr x) instance IOInterfaceFunctionClass SundialsIntegrator where castIOInterfaceFunction (SundialsIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal SundialsIntegrator (Ptr SundialsIntegrator') where marshal (SundialsIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (SundialsIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SundialsIntegrator" c_delete_CasADi__SundialsIntegrator :: FunPtr (Ptr SundialsIntegrator' -> IO ()) instance WrapReturn (Ptr SundialsIntegrator') SundialsIntegrator where wrapReturn = (fmap SundialsIntegrator) . (newForeignPtr c_delete_CasADi__SundialsIntegrator) -- raw decl data QPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass QPSolver where castSharedObject (QPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass QPSolver where castPrintableObject (QPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass QPSolver where castOptionsFunctionality (QPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass QPSolver where castFunction (QPSolver x) = Function (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 Nullspace' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass Nullspace where castSharedObject (Nullspace x) = SharedObject (castForeignPtr x) instance PrintableObjectClass Nullspace where castPrintableObject (Nullspace x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass Nullspace where castOptionsFunctionality (Nullspace x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass Nullspace where castFunction (Nullspace x) = Function (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 IdasIntegrator' -- data decl {-| >[INTERNAL] Interface to IDAS >from the Sundials suite. > >Base class for integrators. 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. > >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 | >+==============+==============+==============+==============+==============+ >| abstol | OT_REAL | 0.000 | Absolute | CasADi::Sund | >| | | | tolerence | ialsInternal | >| | | | for the IVP | | >| | | | solution | | >+--------------+--------------+--------------+--------------+--------------+ >| abstolB | OT_REAL | GenericType( | Absolute | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | adjoint | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | abstol] | | >+--------------+--------------+--------------+--------------+--------------+ >| abstolv | OT_REALVECTO | | | CasADi::Idas | >| | R | | | Internal | >+--------------+--------------+--------------+--------------+--------------+ >| 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. | | >+--------------+--------------+--------------+--------------+--------------+ >| calc_ic | OT_BOOLEAN | true | Use | CasADi::Idas | >| | | | IDACalcIC to | Internal | >| | | | get | | >| | | | consistent | | >| | | | initial | | >| | | | conditions. | | >+--------------+--------------+--------------+--------------+--------------+ >| calc_icB | OT_BOOLEAN | GenericType( | Use | CasADi::Idas | >| | | ) | IDACalcIC to | Internal | >| | | | get | | >| | | | consistent | | >| | | | initial | | >| | | | conditions | | >| | | | for | | >| | | | backwards | | >| | | | system | | >| | | | [default: | | >| | | | equal to | | >| | | | calc_ic]. | | >+--------------+--------------+--------------+--------------+--------------+ >| cj_scaling | OT_BOOLEAN | false | IDAS scaling | CasADi::Idas | >| | | | on cj for | Internal | >| | | | the user- | | >| | | | defined | | >| | | | linear | | >| | | | solver | | >| | | | module | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| disable_inte | OT_BOOLEAN | false | Disable IDAS | CasADi::Idas | >| rnal_warning | | | internal | Internal | >| s | | | warning | | >| | | | messages | | >+--------------+--------------+--------------+--------------+--------------+ >| exact_jacobi | OT_BOOLEAN | true | Use exact | CasADi::Sund | >| an | | | Jacobian | ialsInternal | >| | | | information | | >| | | | for the | | >| | | | forward | | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| exact_jacobi | OT_BOOLEAN | GenericType( | Use exact | CasADi::Sund | >| anB | | ) | Jacobian | ialsInternal | >| | | | information | | >| | | | for the | | >| | | | backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to exa | | >| | | | ct_jacobian] | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_augme | OT_BOOLEAN | true | If DAE | CasADi::Inte | >| nted | | | callback | gratorIntern | >| | | | functions | al | >| | | | are | | >| | | | SXFunction , | | >| | | | have | | >| | | | augmented | | >| | | | DAE callback | | >| | | | function | | >| | | | also be | | >| | | | SXFunction . | | >+--------------+--------------+--------------+--------------+--------------+ >| extra_fsens_ | OT_BOOLEAN | false | Call calc ic | CasADi::Idas | >| calc_ic | | | an extra | Internal | >| | | | time, with | | >| | | | fsens=0 | | >+--------------+--------------+--------------+--------------+--------------+ >| finite_diffe | OT_BOOLEAN | false | Use finite | CasADi::Sund | >| rence_fsens | | | differences | ialsInternal | >| | | | to | | >| | | | approximate | | >| | | | the forward | | >| | | | sensitivity | | >| | | | equations | | >| | | | (if AD is | | >| | | | not | | >| | | | available) | | >+--------------+--------------+--------------+--------------+--------------+ >| first_time | OT_REAL | GenericType( | First | CasADi::Idas | >| | | ) | requested | Internal | >| | | | time as a | | >| | | | fraction of | | >| | | | the time | | >| | | | interval | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_abstol | OT_REAL | GenericType( | Absolute | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | forward | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | abstol] | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_abstol | OT_REALVECTO | | | CasADi::Idas | >| v | R | | | Internal | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_err_co | OT_BOOLEAN | true | include the | CasADi::Sund | >| n | | | forward sens | ialsInternal | >| | | | itivities in | | >| | | | all error | | >| | | | controls | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_reltol | OT_REAL | GenericType( | Relative | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | forward | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | reltol] | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_scalin | OT_REALVECTO | GenericType( | Scaling | CasADi::Sund | >| g_factors | R | ) | factor for | ialsInternal | >| | | | the | | >| | | | components | | >| | | | if finite | | >| | | | differences | | >| | | | is used | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_sensit | OT_INTEGERVE | GenericType( | Specifies | CasADi::Sund | >| iviy_paramet | CTOR | ) | which | ialsInternal | >| ers | | | components | | >| | | | will be used | | >| | | | when | | >| | | | estimating | | >| | | | the | | >| | | | sensitivity | | >| | | | equations | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| init_xdot | OT_REALVECTO | GenericType( | Initial | CasADi::Idas | >| | R | ) | values for | Internal | >| | | | the state | | >| | | | derivatives | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | CasADi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| interpolatio | OT_STRING | "hermite" | Type of inte | CasADi::Sund | >| n_type | | | rpolation | ialsInternal | >| | | | for the | | >| | | | adjoint sens | | >| | | | itivities (h | | >| | | | ermite|polyn | | >| | | | omial) | | >+--------------+--------------+--------------+--------------+--------------+ >| iterative_so | OT_STRING | "gmres" | (gmres|bcgst | CasADi::Sund | >| lver | | | ab|tfqmr) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| iterative_so | OT_STRING | GenericType( | (gmres|bcgst | CasADi::Sund | >| lverB | | ) | ab|tfqmr) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_LINEARSOL | GenericType( | A custom | CasADi::Sund | >| r | VER | ) | linear | ialsInternal | >| | | | solver | | >| | | | creator | | >| | | | function | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_LINEARSOL | GenericType( | A custom | CasADi::Sund | >| rB | VER | ) | linear | ialsInternal | >| | | | solver | | >| | | | creator | | >| | | | function for | | >| | | | backwards | | >| | | | integration | | >| | | | [default: | | >| | | | equal to lin | | >| | | | ear_solver] | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | CasADi::Sund | >| r_options | Y | ) | be passed to | ialsInternal | >| | | | the linear | | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | CasADi::Sund | >| r_optionsB | Y | ) | be passed to | ialsInternal | >| | | | the linear | | >| | | | solver for | | >| | | | backwards | | >| | | | integration | | >| | | | [default: | | >| | | | equal to lin | | >| | | | ear_solver_o | | >| | | | ptions] | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | "dense" | (user_define | CasADi::Sund | >| r_type | | | d|dense|band | ialsInternal | >| | | | ed|iterative | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | GenericType( | (user_define | CasADi::Sund | >| r_typeB | | ) | d|dense|band | ialsInternal | >| | | | ed|iterative | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| lower_bandwi | OT_INTEGER | GenericType( | Lower band- | CasADi::Sund | >| dth | | ) | width of | ialsInternal | >| | | | banded | | >| | | | Jacobian (es | | >| | | | timations) | | >+--------------+--------------+--------------+--------------+--------------+ >| lower_bandwi | OT_INTEGER | GenericType( | lower band- | CasADi::Sund | >| dthB | | ) | width of | ialsInternal | >| | | | banded | | >| | | | jacobians | | >| | | | for backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to low | | >| | | | er_bandwidth | | >| | | | ] | | >+--------------+--------------+--------------+--------------+--------------+ >| max_krylov | OT_INTEGER | 10 | Maximum | CasADi::Sund | >| | | | Krylov | ialsInternal | >| | | | subspace | | >| | | | size | | >+--------------+--------------+--------------+--------------+--------------+ >| max_krylovB | OT_INTEGER | GenericType( | Maximum | CasADi::Sund | >| | | ) | krylov | ialsInternal | >| | | | subspace | | >| | | | size | | >+--------------+--------------+--------------+--------------+--------------+ >| max_multiste | OT_INTEGER | 5 | | CasADi::Sund | >| p_order | | | | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| max_num_step | OT_INTEGER | 10000 | Maximum | CasADi::Sund | >| s | | | number of | ialsInternal | >| | | | integrator | | >| | | | steps | | >+--------------+--------------+--------------+--------------+--------------+ >| max_step_siz | OT_REAL | 0 | Maximim step | CasADi::Idas | >| e | | | size | Internal | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::Idas | >| | | | uts) (corre | Internal | >| | | | ctInitialCon | | >| | | | ditions|res| | | >| | | | resS|resB|rh | | >| | | | sQB|bjacB|jt | | >| | | | imesB|psetup | | >| | | | B|psolveB|ps | | >| | | | etup) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | CasADi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| pretype | OT_STRING | "none" | (none|left|r | CasADi::Sund | >| | | | ight|both) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| pretypeB | OT_STRING | GenericType( | (none|left|r | CasADi::Sund | >| | | ) | ight|both) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| print_stats | OT_BOOLEAN | false | Print out | CasADi::Inte | >| | | | statistics | gratorIntern | >| | | | after | al | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| quad_err_con | OT_BOOLEAN | false | Should the | CasADi::Sund | >| | | | quadratures | ialsInternal | >| | | | affect the | | >| | | | step size | | >| | | | control | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| reltol | OT_REAL | 0.000 | Relative | CasADi::Sund | >| | | | tolerence | ialsInternal | >| | | | for the IVP | | >| | | | solution | | >+--------------+--------------+--------------+--------------+--------------+ >| reltolB | OT_REAL | GenericType( | Relative | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | adjoint | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | reltol] | | >+--------------+--------------+--------------+--------------+--------------+ >| sensitivity_ | OT_STRING | "simultaneou | (simultaneou | CasADi::Sund | >| method | | s" | s|staggered) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| steps_per_ch | OT_INTEGER | 20 | Number of | CasADi::Sund | >| eckpoint | | | steps | ialsInternal | >| | | | between two | | >| | | | consecutive | | >| | | | checkpoints | | >+--------------+--------------+--------------+--------------+--------------+ >| stop_at_end | OT_BOOLEAN | true | Stop the | CasADi::Sund | >| | | | integrator | ialsInternal | >| | | | at the end | | >| | | | of the | | >| | | | interval | | >+--------------+--------------+--------------+--------------+--------------+ >| suppress_alg | OT_BOOLEAN | false | Supress | CasADi::Idas | >| ebraic | | | algebraic | Internal | >| | | | variables in | | >| | | | the error | | >| | | | testing | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| upper_bandwi | OT_INTEGER | GenericType( | Upper band- | CasADi::Sund | >| dth | | ) | width of | ialsInternal | >| | | | banded | | >| | | | Jacobian (es | | >| | | | timations) | | >+--------------+--------------+--------------+--------------+--------------+ >| upper_bandwi | OT_INTEGER | GenericType( | Upper band- | CasADi::Sund | >| dthB | | ) | width of | ialsInternal | >| | | | banded | | >| | | | jacobians | | >| | | | for backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to upp | | >| | | | er_bandwidth | | >| | | | ] | | >+--------------+--------------+--------------+--------------+--------------+ >| use_precondi | OT_BOOLEAN | false | Precondition | CasADi::Sund | >| tioner | | | an iterative | ialsInternal | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| use_precondi | OT_BOOLEAN | GenericType( | Precondition | CasADi::Sund | >| tionerB | | ) | an iterative | ialsInternal | >| | | | solver for | | >| | | | the | | >| | | | backwards | | >| | | | problem | | >| | | | [default: | | >| | | | equal to use | | >| | | | _preconditio | | >| | | | ner] | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+==========================+==========================+ >| bjacB | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| correctInitialConditions | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| inputs | CasADi::FunctionInternal | >+--------------------------+--------------------------+ >| jtimesB | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| outputs | CasADi::FunctionInternal | >+--------------------------+--------------------------+ >| psetup | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| psetupB | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| psolveB | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| res | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| resB | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| resS | CasADi::IdasInternal | >+--------------------------+--------------------------+ >| rhsQB | CasADi::IdasInternal | >+--------------------------+--------------------------+ > >>List of available stats >+-------------+----------------------+ >| Id | Used in | >+=============+======================+ >| nlinsetups | CasADi::IdasInternal | >+-------------+----------------------+ >| nlinsetupsB | CasADi::IdasInternal | >+-------------+----------------------+ >| nsteps | CasADi::IdasInternal | >+-------------+----------------------+ >| nstepsB | CasADi::IdasInternal | >+-------------+----------------------+ > >Diagrams > >C++ includes: idas_integrator.hpp -} newtype IdasIntegrator = IdasIntegrator (ForeignPtr IdasIntegrator') -- typeclass decl class IdasIntegratorClass a where castIdasIntegrator :: a -> IdasIntegrator instance IdasIntegratorClass IdasIntegrator where castIdasIntegrator = id -- baseclass instances instance SharedObjectClass IdasIntegrator where castSharedObject (IdasIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass IdasIntegrator where castPrintableObject (IdasIntegrator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass IdasIntegrator where castOptionsFunctionality (IdasIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass IdasIntegrator where castFunction (IdasIntegrator x) = Function (castForeignPtr x) instance IntegratorClass IdasIntegrator where castIntegrator (IdasIntegrator x) = Integrator (castForeignPtr x) instance SundialsIntegratorClass IdasIntegrator where castSundialsIntegrator (IdasIntegrator x) = SundialsIntegrator (castForeignPtr x) instance IOInterfaceFunctionClass IdasIntegrator where castIOInterfaceFunction (IdasIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal IdasIntegrator (Ptr IdasIntegrator') where marshal (IdasIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (IdasIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__IdasIntegrator" c_delete_CasADi__IdasIntegrator :: FunPtr (Ptr IdasIntegrator' -> IO ()) instance WrapReturn (Ptr IdasIntegrator') IdasIntegrator where wrapReturn = (fmap IdasIntegrator) . (newForeignPtr c_delete_CasADi__IdasIntegrator) -- raw decl data ExpSXElement' -- data decl {-| >[INTERNAL] Expression >interface. > >This is a common base class for SX, MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. Joel Andersson > >C++ includes: generic_expression.hpp -} newtype ExpSXElement = ExpSXElement (ForeignPtr ExpSXElement') -- typeclass decl class ExpSXElementClass a where castExpSXElement :: a -> ExpSXElement instance ExpSXElementClass ExpSXElement where castExpSXElement = id -- baseclass instances -- helper instances instance Marshal ExpSXElement (Ptr ExpSXElement') where marshal (ExpSXElement x) = return (unsafeForeignPtrToPtr x) marshalFree (ExpSXElement x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericExpression_CasADi__SXElement_" c_delete_CasADi__GenericExpression_CasADi__SXElement_ :: FunPtr (Ptr ExpSXElement' -> IO ()) instance WrapReturn (Ptr ExpSXElement') ExpSXElement where wrapReturn = (fmap ExpSXElement) . (newForeignPtr c_delete_CasADi__GenericExpression_CasADi__SXElement_) -- raw decl data NewtonImplicitSolver' -- data decl {-| >[INTERNAL] Implements >simple newton iterations to solve an implicit function. > >The equation: > >F(z, x1, x2, ..., xn) == 0 > >where d_F/dz is invertable, 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. > >Joris Gillis > >>List of available options >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| abstol | OT_REAL | 0.000 | Stopping | CasADi::Newt | >| | | | criterion | onImplicitIn | >| | | | tolerance on | ternal | >| | | | max(|F|) | | >+--------------+--------------+--------------+--------------+--------------+ >| abstolStep | OT_REAL | 0.000 | Stopping | CasADi::Newt | >| | | | criterion | onImplicitIn | >| | | | tolerance on | ternal | >| | | | step size | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >| | | | wether | | >| | | | 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. | | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter | OT_INTEGER | 1000 | Maximum | CasADi::Newt | >| | | | number of | onImplicitIn | >| | | | Newton | ternal | >| | | | iterations | | >| | | | to perform | | >| | | | before | | >| | | | returning. | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::Newt | >| | | | uts) (step| | onImplicitIn | >| | | | stepsize|J|F | ternal | >| | | | |normF) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+==========+================================+ >| F | CasADi::NewtonImplicitInternal | >+----------+--------------------------------+ >| J | CasADi::NewtonImplicitInternal | >+----------+--------------------------------+ >| inputs | CasADi::FunctionInternal | >+----------+--------------------------------+ >| normF | CasADi::NewtonImplicitInternal | >+----------+--------------------------------+ >| outputs | CasADi::FunctionInternal | >+----------+--------------------------------+ >| step | CasADi::NewtonImplicitInternal | >+----------+--------------------------------+ >| stepsize | CasADi::NewtonImplicitInternal | >+----------+--------------------------------+ > >>List of available stats >+---------------+--------------------------------+ >| Id | Used in | >+===============+================================+ >| iter | CasADi::NewtonImplicitInternal | >+---------------+--------------------------------+ >| return_status | CasADi::NewtonImplicitInternal | >+---------------+--------------------------------+ > >Diagrams > >C++ includes: newton_implicit_solver.hpp -} newtype NewtonImplicitSolver = NewtonImplicitSolver (ForeignPtr NewtonImplicitSolver') -- typeclass decl class NewtonImplicitSolverClass a where castNewtonImplicitSolver :: a -> NewtonImplicitSolver instance NewtonImplicitSolverClass NewtonImplicitSolver where castNewtonImplicitSolver = id -- baseclass instances instance SharedObjectClass NewtonImplicitSolver where castSharedObject (NewtonImplicitSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass NewtonImplicitSolver where castPrintableObject (NewtonImplicitSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass NewtonImplicitSolver where castOptionsFunctionality (NewtonImplicitSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass NewtonImplicitSolver where castFunction (NewtonImplicitSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass NewtonImplicitSolver where castIOInterfaceFunction (NewtonImplicitSolver x) = IOInterfaceFunction (castForeignPtr x) instance ImplicitFunctionClass NewtonImplicitSolver where castImplicitFunction (NewtonImplicitSolver x) = ImplicitFunction (castForeignPtr x) -- helper instances instance Marshal NewtonImplicitSolver (Ptr NewtonImplicitSolver') where marshal (NewtonImplicitSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (NewtonImplicitSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__NewtonImplicitSolver" c_delete_CasADi__NewtonImplicitSolver :: FunPtr (Ptr NewtonImplicitSolver' -> IO ()) instance WrapReturn (Ptr NewtonImplicitSolver') NewtonImplicitSolver where wrapReturn = (fmap NewtonImplicitSolver) . (newForeignPtr c_delete_CasADi__NewtonImplicitSolver) -- raw decl data KinsolSolver' -- data decl {-| >[INTERNAL] Kinsol solver >class. > >The equation: > >F(z, x1, x2, ..., xn) == 0 > >where d_F/dz is invertable, 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. You can provide an initial guess by setting output(0). A >good initial guess may be needed to avoid errors like "The linear solver's >setup function failed in an unrecoverable manner." > >The constraints option expects an integer entry for each variable u: 0 then >no constraint is imposed on ui. 1 then ui will be constrained to be ui >= >0.0. 1 then ui will be constrained to be ui <= 0.0. 2 then ui will be >constrained to be ui > 0.0. 2 then ui will be constrained to be ui < 0.0. > >See: ImplicitFunction for more information > >>List of available options >+--------------+--------------+--------------+--------------+--------------+ >| Id | Type | Default | Description | Used in | >+==============+==============+==============+==============+==============+ >| abstol | OT_REAL | 0.000 | Stopping | CasADi::Kins | >| | | | criterion | olInternal | >| | | | tolerance | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| disable_inte | OT_BOOLEAN | false | Disable | CasADi::Kins | >| rnal_warning | | | KINSOL | olInternal | >| s | | | internal | | >| | | | warning | | >| | | | messages | | >+--------------+--------------+--------------+--------------+--------------+ >| exact_jacobi | OT_BOOLEAN | true | | CasADi::Kins | >| an | | | | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| f_scale | OT_REALVECTO | | | CasADi::Kins | >| | R | | | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| iterative_so | OT_STRING | "gmres" | gmres|bcgsta | CasADi::Kins | >| lver | | | b|tfqmr | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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. | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | "dense" | dense|banded | CasADi::Kins | >| r_type | | | |iterative|u | olInternal | >| | | | ser_defined | | >+--------------+--------------+--------------+--------------+--------------+ >| lower_bandwi | OT_INTEGER | | | CasADi::Kins | >| dth | | | | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter | OT_INTEGER | 0 | Maximum | CasADi::Kins | >| | | | number of | olInternal | >| | | | Newton | | >| | | | iterations. | | >| | | | Putting 0 | | >| | | | sets the | | >| | | | default | | >| | | | value of | | >| | | | KinSol. | | >+--------------+--------------+--------------+--------------+--------------+ >| max_krylov | OT_INTEGER | 0 | | CasADi::Kins | >| | | | | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::Kins | >| | | | uts) (eval_ | olInternal | >| | | | f|eval_djac) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | CasADi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| pretype | OT_STRING | "none" | (none|left|r | CasADi::Kins | >| | | | ight|both) | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| strategy | OT_STRING | "none" | Globalizatio | CasADi::Kins | >| | | | n strategy ( | olInternal | >| | | | none|linesea | | >| | | | rch) | | >+--------------+--------------+--------------+--------------+--------------+ >| u_scale | OT_REALVECTO | | | CasADi::Kins | >| | R | | | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| upper_bandwi | OT_INTEGER | | | CasADi::Kins | >| dth | | | | olInternal | >+--------------+--------------+--------------+--------------+--------------+ >| use_precondi | OT_BOOLEAN | false | precondition | CasADi::Kins | >| tioner | | | an iterative | olInternal | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+===========+==========================+ >| eval_djac | CasADi::KinsolInternal | >+-----------+--------------------------+ >| eval_f | CasADi::KinsolInternal | >+-----------+--------------------------+ >| inputs | CasADi::FunctionInternal | >+-----------+--------------------------+ >| outputs | CasADi::FunctionInternal | >+-----------+--------------------------+ > >Diagrams > >C++ includes: kinsol_solver.hpp -} newtype KinsolSolver = KinsolSolver (ForeignPtr KinsolSolver') -- typeclass decl class KinsolSolverClass a where castKinsolSolver :: a -> KinsolSolver instance KinsolSolverClass KinsolSolver where castKinsolSolver = id -- baseclass instances instance SharedObjectClass KinsolSolver where castSharedObject (KinsolSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass KinsolSolver where castPrintableObject (KinsolSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass KinsolSolver where castOptionsFunctionality (KinsolSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass KinsolSolver where castFunction (KinsolSolver x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass KinsolSolver where castIOInterfaceFunction (KinsolSolver x) = IOInterfaceFunction (castForeignPtr x) instance ImplicitFunctionClass KinsolSolver where castImplicitFunction (KinsolSolver x) = ImplicitFunction (castForeignPtr x) -- helper instances instance Marshal KinsolSolver (Ptr KinsolSolver') where marshal (KinsolSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (KinsolSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__KinsolSolver" c_delete_CasADi__KinsolSolver :: FunPtr (Ptr KinsolSolver' -> IO ()) instance WrapReturn (Ptr KinsolSolver') KinsolSolver where wrapReturn = (fmap KinsolSolver) . (newForeignPtr c_delete_CasADi__KinsolSolver) -- raw decl data QPStructure' -- data decl {-| >[INTERNAL] Helper >function for 'QPStruct' > >C++ includes: casadi_types.hpp -} newtype QPStructure = QPStructure (ForeignPtr QPStructure') -- typeclass decl class QPStructureClass a where castQPStructure :: a -> QPStructure instance QPStructureClass QPStructure where castQPStructure = id -- baseclass instances instance PrintableObjectClass QPStructure where castPrintableObject (QPStructure x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal QPStructure (Ptr QPStructure') where marshal (QPStructure x) = return (unsafeForeignPtrToPtr x) marshalFree (QPStructure x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__QPStructIOSchemeVector_CasADi__Sparsity_" c_delete_CasADi__QPStructIOSchemeVector_CasADi__Sparsity_ :: FunPtr (Ptr QPStructure' -> IO ()) instance WrapReturn (Ptr QPStructure') QPStructure where wrapReturn = (fmap QPStructure) . (newForeignPtr c_delete_CasADi__QPStructIOSchemeVector_CasADi__Sparsity_) -- raw decl data CasadiMeta' -- data decl {-| >[INTERNAL] 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 SymbolicQR' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass SymbolicQR where castSharedObject (SymbolicQR x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SymbolicQR where castPrintableObject (SymbolicQR x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SymbolicQR where castOptionsFunctionality (SymbolicQR x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SymbolicQR where castFunction (SymbolicQR x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass SymbolicQR where castIOInterfaceFunction (SymbolicQR x) = IOInterfaceFunction (castForeignPtr x) instance LinearSolverClass SymbolicQR where castLinearSolver (SymbolicQR x) = LinearSolver (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 DirectSingleShooting' -- data decl {-| >[INTERNAL] Direct >Single Shooting. > >ns: Number of shooting nodes: from option number_of_grid_points nx: Number >of differential states: from ffcn.input(INTEGRATOR_X0).size() nc: Number of >constants during intergation: ffcn.input(INTEGRATOR_P).size() nu: Number of >controls: from nc - np np: Number of parameters: from option >number_of_parameters nh: Number of point constraints: from >cfcn.input(0).size() > >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 | >| | | | wether | | >| | | | 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::Dire | >| | R | ) | integrator | ctSingleShoo | >| | | | creator | tingInternal | >| | | | function | | >+--------------+--------------+--------------+--------------+--------------+ >| integrator_o | OT_DICTIONAR | GenericType( | Options to | CasADi::Dire | >| ptions | Y | ) | be passed to | ctSingleShoo | >| | | | the | tingInternal | >| | | | integrator | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver | OT_NLPSOLVER | GenericType( | An NLPSolver | CasADi::Dire | >| | | ) | creator | ctSingleShoo | >| | | | function | tingInternal | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::Dire | >| ptions | Y | ) | be passed to | ctSingleShoo | >| | | | the NLP | tingInternal | >| | | | Solver | | >+--------------+--------------+--------------+--------------+--------------+ >| number_of_gr | OT_INTEGER | 20 | | CasADi::OCPS | >| id_points | | | | olverInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| number_of_pa | OT_INTEGER | 0 | | CasADi::OCPS | >| rameters | | | | olverInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| parallelizat | OT_STRING | GenericType( | Passed on to | CasADi::Dire | >| ion | | ) | CasADi::Para | ctSingleShoo | >| | | | llelizer | tingInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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: direct_single_shooting.hpp -} newtype DirectSingleShooting = DirectSingleShooting (ForeignPtr DirectSingleShooting') -- typeclass decl class DirectSingleShootingClass a where castDirectSingleShooting :: a -> DirectSingleShooting instance DirectSingleShootingClass DirectSingleShooting where castDirectSingleShooting = id -- baseclass instances instance SharedObjectClass DirectSingleShooting where castSharedObject (DirectSingleShooting x) = SharedObject (castForeignPtr x) instance PrintableObjectClass DirectSingleShooting where castPrintableObject (DirectSingleShooting x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass DirectSingleShooting where castOptionsFunctionality (DirectSingleShooting x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass DirectSingleShooting where castFunction (DirectSingleShooting x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass DirectSingleShooting where castIOInterfaceFunction (DirectSingleShooting x) = IOInterfaceFunction (castForeignPtr x) instance OCPSolverClass DirectSingleShooting where castOCPSolver (DirectSingleShooting x) = OCPSolver (castForeignPtr x) -- helper instances instance Marshal DirectSingleShooting (Ptr DirectSingleShooting') where marshal (DirectSingleShooting x) = return (unsafeForeignPtrToPtr x) marshalFree (DirectSingleShooting x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__DirectSingleShooting" c_delete_CasADi__DirectSingleShooting :: FunPtr (Ptr DirectSingleShooting' -> IO ()) instance WrapReturn (Ptr DirectSingleShooting') DirectSingleShooting where wrapReturn = (fmap DirectSingleShooting) . (newForeignPtr c_delete_CasADi__DirectSingleShooting) -- raw decl data SX' -- data decl {-| >[INTERNAL] Sparse matrix class. SX >and DMatrix are specializations. > >General sparse matrix class that is designed with the idea that "everything >is a matrix", that is, also scalars and vectors. This philosophy makes it >easy to use and to interface in particularily with Python and Matlab/Octave. >Index starts with 0. Index vec happens as follows: (rr,cc) -> k = >rr+cc*size1() Vectors are column vectors. The storage format is Compressed >Column Storage (CCS), similar to that used for sparse matrices in Matlab, >but unlike this format, we do allow for elements to be structurally non-zero >but numerically zero. Matrix is polymorphic with a >std::vector that contain all non- identical-zero elements. The >sparsity can be accessed with Sparsity& sparsity() Joel Andersson > >C++ includes: casadi_types.hpp -} 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) instance GenSXClass SX where castGenSX (SX x) = GenSX (castForeignPtr x) instance ExpSXClass SX where castExpSX (SX x) = ExpSX (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__Matrix_CasADi__SXElement_" c_delete_CasADi__Matrix_CasADi__SXElement_ :: FunPtr (Ptr SX' -> IO ()) instance WrapReturn (Ptr SX') SX where wrapReturn = (fmap SX) . (newForeignPtr c_delete_CasADi__Matrix_CasADi__SXElement_) -- raw decl data DirectMultipleShooting' -- data decl {-| >[INTERNAL] Direct >Multiple Shooting. > >ns: Number of shooting nodes: from option number_of_grid_points nx: Number >of differential states: from ffcn.input(INTEGRATOR_X0).size() nc: Number of >constants during intergation: ffcn.input(INTEGRATOR_P).size() nu: Number of >controls: from nc - np np: Number of parameters: from option >number_of_parameters nh: Number of point constraints: from >cfcn.input(0).size() > >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 | >| | | | wether | | >| | | | 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::Dire | >| | R | ) | integrator | ctMultipleSh | >| | | | creator | ootingIntern | >| | | | function | al | >+--------------+--------------+--------------+--------------+--------------+ >| integrator_o | OT_DICTIONAR | GenericType( | Options to | CasADi::Dire | >| ptions | Y | ) | be passed to | ctMultipleSh | >| | | | the | ootingIntern | >| | | | integrator | al | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver | OT_NLPSOLVER | GenericType( | An NLPSolver | CasADi::Dire | >| | | ) | creator | ctMultipleSh | >| | | | function | ootingIntern | >| | | | | al | >+--------------+--------------+--------------+--------------+--------------+ >| nlp_solver_o | OT_DICTIONAR | GenericType( | Options to | CasADi::Dire | >| ptions | Y | ) | be passed to | ctMultipleSh | >| | | | the NLP | ootingIntern | >| | | | Solver | al | >+--------------+--------------+--------------+--------------+--------------+ >| number_of_gr | OT_INTEGER | 20 | | CasADi::OCPS | >| id_points | | | | olverInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| number_of_pa | OT_INTEGER | 0 | | CasADi::OCPS | >| rameters | | | | olverInterna | >| | | | | l | >+--------------+--------------+--------------+--------------+--------------+ >| parallelizat | OT_STRING | GenericType( | Passed on to | CasADi::Dire | >| ion | | ) | CasADi::Para | ctMultipleSh | >| | | | llelizer | ootingIntern | >| | | | | al | >+--------------+--------------+--------------+--------------+--------------+ >| 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: direct_multiple_shooting.hpp -} newtype DirectMultipleShooting = DirectMultipleShooting (ForeignPtr DirectMultipleShooting') -- typeclass decl class DirectMultipleShootingClass a where castDirectMultipleShooting :: a -> DirectMultipleShooting instance DirectMultipleShootingClass DirectMultipleShooting where castDirectMultipleShooting = id -- baseclass instances instance SharedObjectClass DirectMultipleShooting where castSharedObject (DirectMultipleShooting x) = SharedObject (castForeignPtr x) instance PrintableObjectClass DirectMultipleShooting where castPrintableObject (DirectMultipleShooting x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass DirectMultipleShooting where castOptionsFunctionality (DirectMultipleShooting x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass DirectMultipleShooting where castFunction (DirectMultipleShooting x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass DirectMultipleShooting where castIOInterfaceFunction (DirectMultipleShooting x) = IOInterfaceFunction (castForeignPtr x) instance OCPSolverClass DirectMultipleShooting where castOCPSolver (DirectMultipleShooting x) = OCPSolver (castForeignPtr x) -- helper instances instance Marshal DirectMultipleShooting (Ptr DirectMultipleShooting') where marshal (DirectMultipleShooting x) = return (unsafeForeignPtrToPtr x) marshalFree (DirectMultipleShooting x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__DirectMultipleShooting" c_delete_CasADi__DirectMultipleShooting :: FunPtr (Ptr DirectMultipleShooting' -> IO ()) instance WrapReturn (Ptr DirectMultipleShooting') DirectMultipleShooting where wrapReturn = (fmap DirectMultipleShooting) . (newForeignPtr c_delete_CasADi__DirectMultipleShooting) -- raw decl data IOInterfaceFunction' -- data decl {-| >[INTERNAL] 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_) -- raw decl data SDQPStructure' -- data decl {-| >[INTERNAL] Helper >function for 'SDQPStruct' > >C++ includes: casadi_types.hpp -} newtype SDQPStructure = SDQPStructure (ForeignPtr SDQPStructure') -- typeclass decl class SDQPStructureClass a where castSDQPStructure :: a -> SDQPStructure instance SDQPStructureClass SDQPStructure where castSDQPStructure = id -- baseclass instances instance PrintableObjectClass SDQPStructure where castPrintableObject (SDQPStructure x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SDQPStructure (Ptr SDQPStructure') where marshal (SDQPStructure x) = return (unsafeForeignPtrToPtr x) marshalFree (SDQPStructure x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SDQPStructIOSchemeVector_CasADi__Sparsity_" c_delete_CasADi__SDQPStructIOSchemeVector_CasADi__Sparsity_ :: FunPtr (Ptr SDQPStructure' -> IO ()) instance WrapReturn (Ptr SDQPStructure') SDQPStructure where wrapReturn = (fmap SDQPStructure) . (newForeignPtr c_delete_CasADi__SDQPStructIOSchemeVector_CasADi__Sparsity_) -- raw decl data SDPStructure' -- data decl {-| >[INTERNAL] Helper >function for 'SDPStruct' > >C++ includes: casadi_types.hpp -} newtype SDPStructure = SDPStructure (ForeignPtr SDPStructure') -- typeclass decl class SDPStructureClass a where castSDPStructure :: a -> SDPStructure instance SDPStructureClass SDPStructure where castSDPStructure = id -- baseclass instances instance PrintableObjectClass SDPStructure where castPrintableObject (SDPStructure x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SDPStructure (Ptr SDPStructure') where marshal (SDPStructure x) = return (unsafeForeignPtrToPtr x) marshalFree (SDPStructure x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SDPStructIOSchemeVector_CasADi__Sparsity_" c_delete_CasADi__SDPStructIOSchemeVector_CasADi__Sparsity_ :: FunPtr (Ptr SDPStructure' -> IO ()) instance WrapReturn (Ptr SDPStructure') SDPStructure where wrapReturn = (fmap SDPStructure) . (newForeignPtr c_delete_CasADi__SDPStructIOSchemeVector_CasADi__Sparsity_) -- raw decl data GenDMatrix' -- data decl {-| >[INTERNAL] Matrix base >class. > >This is a common base class for MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. The class is designed with the idea that >"everything is a matrix", that is, also scalars and vectors. This >philosophy makes it easy to use and to interface in particularily with >Python and Matlab/Octave. The syntax tries to stay as close as possible to >the ublas syntax when it comes to vector/matrix operations. Index starts >with 0. Index vec happens as follows: (rr,cc) -> k = rr+cc*size1() Vectors >are column vectors. The storage format is Compressed Column Storage (CCS), >similar to that used for sparse matrices in Matlab, but unlike this format, >we do allow for elements to be structurally non-zero but numerically zero. >The sparsity pattern, which is reference counted and cached, can be accessed >with Sparsity& sparsity() Joel Andersson > >C++ includes: generic_matrix.hpp -} newtype GenDMatrix = GenDMatrix (ForeignPtr GenDMatrix') -- typeclass decl class GenDMatrixClass a where castGenDMatrix :: a -> GenDMatrix instance GenDMatrixClass GenDMatrix where castGenDMatrix = id -- baseclass instances -- helper instances instance Marshal GenDMatrix (Ptr GenDMatrix') where marshal (GenDMatrix x) = return (unsafeForeignPtrToPtr x) marshalFree (GenDMatrix x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericMatrix_CasADi__Matrix_double__" c_delete_CasADi__GenericMatrix_CasADi__Matrix_double__ :: FunPtr (Ptr GenDMatrix' -> IO ()) instance WrapReturn (Ptr GenDMatrix') GenDMatrix where wrapReturn = (fmap GenDMatrix) . (newForeignPtr c_delete_CasADi__GenericMatrix_CasADi__Matrix_double__) -- raw decl data ExpIMatrix' -- data decl {-| >[INTERNAL] Expression >interface. > >This is a common base class for SX, MX and Matrix<>, introducing a uniform >syntax and implementing common functionality using the curiously recurring >template pattern (CRTP) idiom. Joel Andersson > >C++ includes: generic_expression.hpp -} newtype ExpIMatrix = ExpIMatrix (ForeignPtr ExpIMatrix') -- typeclass decl class ExpIMatrixClass a where castExpIMatrix :: a -> ExpIMatrix instance ExpIMatrixClass ExpIMatrix where castExpIMatrix = id -- baseclass instances -- helper instances instance Marshal ExpIMatrix (Ptr ExpIMatrix') where marshal (ExpIMatrix x) = return (unsafeForeignPtrToPtr x) marshalFree (ExpIMatrix x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__GenericExpression_CasADi__Matrix_int__" c_delete_CasADi__GenericExpression_CasADi__Matrix_int__ :: FunPtr (Ptr ExpIMatrix' -> IO ()) instance WrapReturn (Ptr ExpIMatrix') ExpIMatrix where wrapReturn = (fmap ExpIMatrix) . (newForeignPtr c_delete_CasADi__GenericExpression_CasADi__Matrix_int__) -- raw decl data CustomFunction' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass CustomFunction where castSharedObject (CustomFunction x) = SharedObject (castForeignPtr x) instance PrintableObjectClass CustomFunction where castPrintableObject (CustomFunction x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass CustomFunction where castOptionsFunctionality (CustomFunction x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass CustomFunction where castFunction (CustomFunction x) = Function (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 LPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass LPSolver where castSharedObject (LPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass LPSolver where castPrintableObject (LPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass LPSolver where castOptionsFunctionality (LPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass LPSolver where castFunction (LPSolver x) = Function (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 OCPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass OCPSolver where castSharedObject (OCPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass OCPSolver where castPrintableObject (OCPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass OCPSolver where castOptionsFunctionality (OCPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass OCPSolver where castFunction (OCPSolver x) = Function (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 LinearSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass LinearSolver where castSharedObject (LinearSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass LinearSolver where castPrintableObject (LinearSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass LinearSolver where castOptionsFunctionality (LinearSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass LinearSolver where castFunction (LinearSolver x) = Function (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 SymbolicOCP' -- data decl {-| >[INTERNAL] A flat OCP >representation coupled to an XML file. > >Variables: > >x: differential states z: algebraic states p : independent >parameters t : time u : control signals q : quadrature states y : >dependent variables > >Equations: > >explicit or implicit ODE: \\dot{x} = ode(t,x,z,u,p_free,pi,pd) or 0 = >ode(t,x,z,\\dot{x},u,p_free,pi,pd) algebraic equations: 0 = >alg(t,x,z,u,p_free,pi,pd) quadratures: \\dot{q} = >quad(t,x,z,u,p_free,pi,pd) dependent equations: y = >dep(t,x,z,u,p_free,pi,pd) initial equations: 0 = >initial(t,x,z,u,p_free,pi,pd) > >Objective function terms: > >Mayer terms: \\sum{mterm_k} Lagrange terms: >\\sum{\\integral{mterm}} > >Note that when parsed, all dynamic equations end up in the implicit category >"dae". At a later state, the DAE can be reformulated, for example in semi- >explicit form, possibly in addition to a set of quadrature states. > >Usage skeleton: > >Call default constructor SymbolicOCP ocp; > >Parse an FMI conformant XML file ocp.parseFMI(xml_file_name) > >Modify/add variables, equations, optimization ... > >When the optimal control problem is in a suitable form, it is possible to >either generate functions for numeric/symbolic evaluation or exporting the >OCP formulation into a new FMI conformant XML file. The latter functionality >is not yet available. > >Joel Andersson > >C++ includes: symbolic_ocp.hpp -} newtype SymbolicOCP = SymbolicOCP (ForeignPtr SymbolicOCP') -- typeclass decl class SymbolicOCPClass a where castSymbolicOCP :: a -> SymbolicOCP instance SymbolicOCPClass SymbolicOCP where castSymbolicOCP = id -- baseclass instances instance PrintableObjectClass SymbolicOCP where castPrintableObject (SymbolicOCP x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SymbolicOCP (Ptr SymbolicOCP') where marshal (SymbolicOCP x) = return (unsafeForeignPtrToPtr x) marshalFree (SymbolicOCP x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SymbolicOCP" c_delete_CasADi__SymbolicOCP :: FunPtr (Ptr SymbolicOCP' -> IO ()) instance WrapReturn (Ptr SymbolicOCP') SymbolicOCP where wrapReturn = (fmap SymbolicOCP) . (newForeignPtr c_delete_CasADi__SymbolicOCP) -- raw decl data Function' -- data decl {-| >[INTERNAL] 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 is these formulas must be transposed: input col: transpose >$ \\vec{v} $ and $\\vec{s}_a$ output col: transpose $ \\vec{w} $ and >$\\vec{s}_f$ NOTE: Function's are allowed to modify their input arguments >when evaluating: implicitFunction, IDAS solver Futher 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 | >| | | | wether | | >| | | | 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 SharedObjectClass Function where castSharedObject (Function x) = SharedObject (castForeignPtr x) instance PrintableObjectClass Function where castPrintableObject (Function x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass Function where castOptionsFunctionality (Function x) = OptionsFunctionality (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 SOCPSolver' -- data decl {-| >[INTERNAL] 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 | >| | | | wether | | >| | | | 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 SharedObjectClass SOCPSolver where castSharedObject (SOCPSolver x) = SharedObject (castForeignPtr x) instance PrintableObjectClass SOCPSolver where castPrintableObject (SOCPSolver x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass SOCPSolver where castOptionsFunctionality (SOCPSolver x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass SOCPSolver where castFunction (SOCPSolver x) = Function (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 DerivativeGenerator' -- data decl {-| >[INTERNAL] 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 SharedObjectClass DerivativeGenerator where castSharedObject (DerivativeGenerator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass DerivativeGenerator where castPrintableObject (DerivativeGenerator x) = PrintableObject (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 SOCPStructure' -- data decl {-| >[INTERNAL] Helper >function for 'SOCPStruct' > >C++ includes: casadi_types.hpp -} newtype SOCPStructure = SOCPStructure (ForeignPtr SOCPStructure') -- typeclass decl class SOCPStructureClass a where castSOCPStructure :: a -> SOCPStructure instance SOCPStructureClass SOCPStructure where castSOCPStructure = id -- baseclass instances instance PrintableObjectClass SOCPStructure where castPrintableObject (SOCPStructure x) = PrintableObject (castForeignPtr x) -- helper instances instance Marshal SOCPStructure (Ptr SOCPStructure') where marshal (SOCPStructure x) = return (unsafeForeignPtrToPtr x) marshalFree (SOCPStructure x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__SOCPStructIOSchemeVector_CasADi__Sparsity_" c_delete_CasADi__SOCPStructIOSchemeVector_CasADi__Sparsity_ :: FunPtr (Ptr SOCPStructure' -> IO ()) instance WrapReturn (Ptr SOCPStructure') SOCPStructure where wrapReturn = (fmap SOCPStructure) . (newForeignPtr c_delete_CasADi__SOCPStructIOSchemeVector_CasADi__Sparsity_) -- raw decl data ImplicitFunction' -- data decl {-| >[INTERNAL] Abstract base >class for the implicit function classes. > >The equation: > >F(z, x1, x2, ..., xn) == 0 > >where d_F/dz is invertable, 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 | >| | | | wether | | >| | | | 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 SharedObjectClass ImplicitFunction where castSharedObject (ImplicitFunction x) = SharedObject (castForeignPtr x) instance PrintableObjectClass ImplicitFunction where castPrintableObject (ImplicitFunction x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass ImplicitFunction where castOptionsFunctionality (ImplicitFunction x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass ImplicitFunction where castFunction (ImplicitFunction x) = Function (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 CVodesIntegrator' -- data decl {-| >[INTERNAL] Interface to >CVodes from the Sundials suite. > >Base class for integrators. 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. > >A call to evaluate will integrate to the end. > >You can retrieve the entire state trajectory as follows, after the evaluate >call: Call reset. Then call integrate(t_i) and getOuput for a series of >times t_i. > >>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 | >+==============+==============+==============+==============+==============+ >| abstol | OT_REAL | 0.000 | Absolute | CasADi::Sund | >| | | | tolerence | ialsInternal | >| | | | for the IVP | | >| | | | solution | | >+--------------+--------------+--------------+--------------+--------------+ >| abstolB | OT_REAL | GenericType( | Absolute | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | adjoint | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | abstol] | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| disable_inte | OT_BOOLEAN | false | Disable | CasADi::CVod | >| rnal_warning | | | CVodes | esInternal | >| s | | | internal | | >| | | | warning | | >| | | | messages | | >+--------------+--------------+--------------+--------------+--------------+ >| exact_jacobi | OT_BOOLEAN | true | Use exact | CasADi::Sund | >| an | | | Jacobian | ialsInternal | >| | | | information | | >| | | | for the | | >| | | | forward | | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| exact_jacobi | OT_BOOLEAN | GenericType( | Use exact | CasADi::Sund | >| anB | | ) | Jacobian | ialsInternal | >| | | | information | | >| | | | for the | | >| | | | backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to exa | | >| | | | ct_jacobian] | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_augme | OT_BOOLEAN | true | If DAE | CasADi::Inte | >| nted | | | callback | gratorIntern | >| | | | functions | al | >| | | | are | | >| | | | SXFunction , | | >| | | | have | | >| | | | augmented | | >| | | | DAE callback | | >| | | | function | | >| | | | also be | | >| | | | SXFunction . | | >+--------------+--------------+--------------+--------------+--------------+ >| finite_diffe | OT_BOOLEAN | false | Use finite | CasADi::Sund | >| rence_fsens | | | differences | ialsInternal | >| | | | to | | >| | | | approximate | | >| | | | the forward | | >| | | | sensitivity | | >| | | | equations | | >| | | | (if AD is | | >| | | | not | | >| | | | available) | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_abstol | OT_REAL | GenericType( | Absolute | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | forward | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | abstol] | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_all_at | OT_BOOLEAN | true | Calculate | CasADi::CVod | >| _once | | | all right | esInternal | >| | | | hand sides | | >| | | | of the | | >| | | | sensitivity | | >| | | | equations at | | >| | | | once | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_err_co | OT_BOOLEAN | true | include the | CasADi::Sund | >| n | | | forward sens | ialsInternal | >| | | | itivities in | | >| | | | all error | | >| | | | controls | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_reltol | OT_REAL | GenericType( | Relative | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | forward | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | reltol] | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_scalin | OT_REALVECTO | GenericType( | Scaling | CasADi::Sund | >| g_factors | R | ) | factor for | ialsInternal | >| | | | the | | >| | | | components | | >| | | | if finite | | >| | | | differences | | >| | | | is used | | >+--------------+--------------+--------------+--------------+--------------+ >| fsens_sensit | OT_INTEGERVE | GenericType( | Specifies | CasADi::Sund | >| iviy_paramet | CTOR | ) | which | ialsInternal | >| ers | | | components | | >| | | | will be used | | >| | | | when | | >| | | | estimating | | >| | | | the | | >| | | | sensitivity | | >| | | | equations | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| interpolatio | OT_STRING | "hermite" | Type of inte | CasADi::Sund | >| n_type | | | rpolation | ialsInternal | >| | | | for the | | >| | | | adjoint sens | | >| | | | itivities (h | | >| | | | ermite|polyn | | >| | | | omial) | | >+--------------+--------------+--------------+--------------+--------------+ >| iterative_so | OT_STRING | "gmres" | (gmres|bcgst | CasADi::Sund | >| lver | | | ab|tfqmr) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| iterative_so | OT_STRING | GenericType( | (gmres|bcgst | CasADi::Sund | >| lverB | | ) | ab|tfqmr) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| linear_multi | OT_STRING | "bdf" | Integrator | CasADi::CVod | >| step_method | | | scheme | esInternal | >| | | | (bdf|adams) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_LINEARSOL | GenericType( | A custom | CasADi::Sund | >| r | VER | ) | linear | ialsInternal | >| | | | solver | | >| | | | creator | | >| | | | function | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_LINEARSOL | GenericType( | A custom | CasADi::Sund | >| rB | VER | ) | linear | ialsInternal | >| | | | solver | | >| | | | creator | | >| | | | function for | | >| | | | backwards | | >| | | | integration | | >| | | | [default: | | >| | | | equal to lin | | >| | | | ear_solver] | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | CasADi::Sund | >| r_options | Y | ) | be passed to | ialsInternal | >| | | | the linear | | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_DICTIONAR | GenericType( | Options to | CasADi::Sund | >| r_optionsB | Y | ) | be passed to | ialsInternal | >| | | | the linear | | >| | | | solver for | | >| | | | backwards | | >| | | | integration | | >| | | | [default: | | >| | | | equal to lin | | >| | | | ear_solver_o | | >| | | | ptions] | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | "dense" | (user_define | CasADi::Sund | >| r_type | | | d|dense|band | ialsInternal | >| | | | ed|iterative | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_solve | OT_STRING | GenericType( | (user_define | CasADi::Sund | >| r_typeB | | ) | d|dense|band | ialsInternal | >| | | | ed|iterative | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| lower_bandwi | OT_INTEGER | GenericType( | Lower band- | CasADi::Sund | >| dth | | ) | width of | ialsInternal | >| | | | banded | | >| | | | Jacobian (es | | >| | | | timations) | | >+--------------+--------------+--------------+--------------+--------------+ >| lower_bandwi | OT_INTEGER | GenericType( | lower band- | CasADi::Sund | >| dthB | | ) | width of | ialsInternal | >| | | | banded | | >| | | | jacobians | | >| | | | for backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to low | | >| | | | er_bandwidth | | >| | | | ] | | >+--------------+--------------+--------------+--------------+--------------+ >| max_krylov | OT_INTEGER | 10 | Maximum | CasADi::Sund | >| | | | Krylov | ialsInternal | >| | | | subspace | | >| | | | size | | >+--------------+--------------+--------------+--------------+--------------+ >| max_krylovB | OT_INTEGER | GenericType( | Maximum | CasADi::Sund | >| | | ) | krylov | ialsInternal | >| | | | subspace | | >| | | | size | | >+--------------+--------------+--------------+--------------+--------------+ >| max_multiste | OT_INTEGER | 5 | | CasADi::Sund | >| p_order | | | | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| max_num_step | OT_INTEGER | 10000 | Maximum | CasADi::Sund | >| s | | | number of | ialsInternal | >| | | | integrator | | >| | | | steps | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::CVod | >| | | | uts) (res|r | esInternal | >| | | | esB|resQB|re | | >| | | | set|psetupB| | | >| | | | djacB) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | CasADi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| nonlinear_so | OT_STRING | "newton" | (newton|func | CasADi::CVod | >| lver_iterati | | | tional) | esInternal | >| on | | | | | >+--------------+--------------+--------------+--------------+--------------+ >| pretype | OT_STRING | "none" | (none|left|r | CasADi::Sund | >| | | | ight|both) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| pretypeB | OT_STRING | GenericType( | (none|left|r | CasADi::Sund | >| | | ) | ight|both) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| print_stats | OT_BOOLEAN | false | Print out | CasADi::Inte | >| | | | statistics | gratorIntern | >| | | | after | al | >| | | | integration | | >+--------------+--------------+--------------+--------------+--------------+ >| quad_err_con | OT_BOOLEAN | false | Should the | CasADi::Sund | >| | | | quadratures | ialsInternal | >| | | | affect the | | >| | | | step size | | >| | | | control | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| reltol | OT_REAL | 0.000 | Relative | CasADi::Sund | >| | | | tolerence | ialsInternal | >| | | | for the IVP | | >| | | | solution | | >+--------------+--------------+--------------+--------------+--------------+ >| reltolB | OT_REAL | GenericType( | Relative | CasADi::Sund | >| | | ) | tolerence | ialsInternal | >| | | | for the | | >| | | | adjoint | | >| | | | sensitivity | | >| | | | solution | | >| | | | [default: | | >| | | | equal to | | >| | | | reltol] | | >+--------------+--------------+--------------+--------------+--------------+ >| sensitivity_ | OT_STRING | "simultaneou | (simultaneou | CasADi::Sund | >| method | | s" | s|staggered) | ialsInternal | >+--------------+--------------+--------------+--------------+--------------+ >| steps_per_ch | OT_INTEGER | 20 | Number of | CasADi::Sund | >| eckpoint | | | steps | ialsInternal | >| | | | between two | | >| | | | consecutive | | >| | | | checkpoints | | >+--------------+--------------+--------------+--------------+--------------+ >| stop_at_end | OT_BOOLEAN | true | Stop the | CasADi::Sund | >| | | | integrator | ialsInternal | >| | | | at the end | | >| | | | of the | | >| | | | interval | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+--------------+--------------+--------------+--------------+--------------+ >| upper_bandwi | OT_INTEGER | GenericType( | Upper band- | CasADi::Sund | >| dth | | ) | width of | ialsInternal | >| | | | banded | | >| | | | Jacobian (es | | >| | | | timations) | | >+--------------+--------------+--------------+--------------+--------------+ >| upper_bandwi | OT_INTEGER | GenericType( | Upper band- | CasADi::Sund | >| dthB | | ) | width of | ialsInternal | >| | | | banded | | >| | | | jacobians | | >| | | | for backward | | >| | | | integration | | >| | | | [default: | | >| | | | equal to upp | | >| | | | er_bandwidth | | >| | | | ] | | >+--------------+--------------+--------------+--------------+--------------+ >| use_precondi | OT_BOOLEAN | false | Precondition | CasADi::Sund | >| tioner | | | an iterative | ialsInternal | >| | | | solver | | >+--------------+--------------+--------------+--------------+--------------+ >| use_precondi | OT_BOOLEAN | GenericType( | Precondition | CasADi::Sund | >| tionerB | | ) | an iterative | ialsInternal | >| | | | solver for | | >| | | | the | | >| | | | backwards | | >| | | | problem | | >| | | | [default: | | >| | | | equal to use | | >| | | | _preconditio | | >| | | | ner] | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >+=========+==========================+ >| djacB | CasADi::CVodesInternal | >+---------+--------------------------+ >| inputs | CasADi::FunctionInternal | >+---------+--------------------------+ >| outputs | CasADi::FunctionInternal | >+---------+--------------------------+ >| psetupB | CasADi::CVodesInternal | >+---------+--------------------------+ >| res | CasADi::CVodesInternal | >+---------+--------------------------+ >| resB | CasADi::CVodesInternal | >+---------+--------------------------+ >| resQB | CasADi::CVodesInternal | >+---------+--------------------------+ >| reset | CasADi::CVodesInternal | >+---------+--------------------------+ > >>List of available stats >+-------------+------------------------+ >| Id | Used in | >+=============+========================+ >| nlinsetups | CasADi::CVodesInternal | >+-------------+------------------------+ >| nlinsetupsB | CasADi::CVodesInternal | >+-------------+------------------------+ >| nsteps | CasADi::CVodesInternal | >+-------------+------------------------+ >| nstepsB | CasADi::CVodesInternal | >+-------------+------------------------+ > >Diagrams > >C++ includes: cvodes_integrator.hpp -} newtype CVodesIntegrator = CVodesIntegrator (ForeignPtr CVodesIntegrator') -- typeclass decl class CVodesIntegratorClass a where castCVodesIntegrator :: a -> CVodesIntegrator instance CVodesIntegratorClass CVodesIntegrator where castCVodesIntegrator = id -- baseclass instances instance SharedObjectClass CVodesIntegrator where castSharedObject (CVodesIntegrator x) = SharedObject (castForeignPtr x) instance PrintableObjectClass CVodesIntegrator where castPrintableObject (CVodesIntegrator x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass CVodesIntegrator where castOptionsFunctionality (CVodesIntegrator x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass CVodesIntegrator where castFunction (CVodesIntegrator x) = Function (castForeignPtr x) instance IntegratorClass CVodesIntegrator where castIntegrator (CVodesIntegrator x) = Integrator (castForeignPtr x) instance SundialsIntegratorClass CVodesIntegrator where castSundialsIntegrator (CVodesIntegrator x) = SundialsIntegrator (castForeignPtr x) instance IOInterfaceFunctionClass CVodesIntegrator where castIOInterfaceFunction (CVodesIntegrator x) = IOInterfaceFunction (castForeignPtr x) -- helper instances instance Marshal CVodesIntegrator (Ptr CVodesIntegrator') where marshal (CVodesIntegrator x) = return (unsafeForeignPtrToPtr x) marshalFree (CVodesIntegrator x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__CVodesIntegrator" c_delete_CasADi__CVodesIntegrator :: FunPtr (Ptr CVodesIntegrator' -> IO ()) instance WrapReturn (Ptr CVodesIntegrator') CVodesIntegrator where wrapReturn = (fmap CVodesIntegrator) . (newForeignPtr c_delete_CasADi__CVodesIntegrator) -- raw decl data IndexList' -- data decl {-| >[INTERNAL] Class representing a >non-regular (and thus non-slice) index list > >C++ includes: slice.hpp -} newtype IndexList = IndexList (ForeignPtr IndexList') -- typeclass decl class IndexListClass a where castIndexList :: a -> IndexList instance IndexListClass IndexList where castIndexList = id -- baseclass instances -- helper instances instance Marshal IndexList (Ptr IndexList') where marshal (IndexList x) = return (unsafeForeignPtrToPtr x) marshalFree (IndexList x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__IndexList" c_delete_CasADi__IndexList :: FunPtr (Ptr IndexList' -> IO ()) instance WrapReturn (Ptr IndexList') IndexList where wrapReturn = (fmap IndexList) . (newForeignPtr c_delete_CasADi__IndexList) -- raw decl data StabilizedSQPMethod' -- data decl {-| >[INTERNAL] Stabilized >Sequential Quadratic Programming method. > >Slava Kung > >>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 | >+==============+==============+==============+==============+==============+ >| TReta1 | OT_REAL | 0.800 | Required | CasADi::Stab | >| | | | predicted / | ilizedSQPInt | >| | | | actual | ernal | >| | | | decrease for | | >| | | | TR increase | | >+--------------+--------------+--------------+--------------+--------------+ >| TReta2 | OT_REAL | 0.200 | Required | CasADi::Stab | >| | | | predicted / | ilizedSQPInt | >| | | | actual | ernal | >| | | | decrease for | | >| | | | TR decrease | | >+--------------+--------------+--------------+--------------+--------------+ >| 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) | | >+--------------+--------------+--------------+--------------+--------------+ >| alphaMin | OT_REAL | 0.001 | Used to | CasADi::Stab | >| | | | check | ilizedSQPInt | >| | | | whether to | ernal | >| | | | increase | | >| | | | rho. | | >+--------------+--------------+--------------+--------------+--------------+ >| beta | OT_REAL | 0.500 | Line-search | CasADi::Stab | >| | | | parameter, | ilizedSQPInt | >| | | | restoration | ernal | >| | | | factor of | | >| | | | stepsize | | >+--------------+--------------+--------------+--------------+--------------+ >| c1 | OT_REAL | 0.001 | Armijo | CasADi::Stab | >| | | | condition, | ilizedSQPInt | >| | | | coefficient | ernal | >| | | | of decrease | | >| | | | in merit | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| dvMax0 | OT_REAL | 100 | Parameter | CasADi::Stab | >| | | | used to | ilizedSQPInt | >| | | | defined the | ernal | >| | | | max step | | >| | | | length. | | >+--------------+--------------+--------------+--------------+--------------+ >| eps_active | OT_REAL | 0.000 | Threshold | CasADi::Stab | >| | | | for the | ilizedSQPInt | >| | | | epsilon- | ernal | >| | | | active set. | | >+--------------+--------------+--------------+--------------+--------------+ >| expand | OT_BOOLEAN | false | Expand the | CasADi::NLPS | >| | | | NLP function | olverInterna | >| | | | in terms of | l | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_f | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | objective | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| expand_g | OT_BOOLEAN | GenericType( | Expand the | CasADi::NLPS | >| | | ) | constraint | olverInterna | >| | | | function in | l | >| | | | terms of | | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX. | | >| | | | Deprecated, | | >| | | | use "expand" | | >| | | | instead. | | >+--------------+--------------+--------------+--------------+--------------+ >| gamma1 | OT_REAL | 2 | Trust region | CasADi::Stab | >| | | | increase | ilizedSQPInt | >| | | | parameter | ernal | >+--------------+--------------+--------------+--------------+--------------+ >| gamma2 | OT_REAL | 1 | Trust region | CasADi::Stab | >| | | | update | ilizedSQPInt | >| | | | parameter | ernal | >+--------------+--------------+--------------+--------------+--------------+ >| gamma3 | OT_REAL | 1 | Trust region | CasADi::Stab | >| | | | decrease | ilizedSQPInt | >| | | | parameter | ernal | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | CasADi::Func | >| | | | indicate | tionInternal | >| | | | wether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| gauss_newton | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. Use | olverInterna | >| | | | Gauss Newton | l | >| | | | Hessian appr | | >| | | | oximation | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_gra | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| dient | | ) | option. | olverInterna | >| | | | Generate a | l | >| | | | function for | | >| | | | calculating | | >| | | | the gradient | | >| | | | of the | | >| | | | objective. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_hes | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| sian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Hessian of | | >| | | | the | | >| | | | Lagrangian | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| generate_jac | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| obian | | ) | option. | olverInterna | >| | | | Generate an | l | >| | | | exact | | >| | | | Jacobian of | | >| | | | the | | >| | | | constraints | | >| | | | if not | | >| | | | supplied. | | >+--------------+--------------+--------------+--------------+--------------+ >| hessian_appr | OT_STRING | "exact" | limited- | CasADi::Stab | >| oximation | | | memory|exact | ilizedSQPInt | >| | | | | ernal | >+--------------+--------------+--------------+--------------+--------------+ >| 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. | | >+--------------+--------------+--------------+--------------+--------------+ >| lbfgs_memory | OT_INTEGER | 10 | Size of | CasADi::Stab | >| | | | L-BFGS | ilizedSQPInt | >| | | | memory. | ernal | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter | OT_INTEGER | 100 | Maximum | CasADi::Stab | >| | | | number of | ilizedSQPInt | >| | | | SQP | ernal | >| | | | iterations | | >+--------------+--------------+--------------+--------------+--------------+ >| max_iter_ls | OT_INTEGER | 20 | Maximum | CasADi::Stab | >| | | | number of | ilizedSQPInt | >| | | | linesearch | ernal | >| | | | iterations | | >+--------------+--------------+--------------+--------------+--------------+ >| merit_memory | OT_INTEGER | 4 | Size of | CasADi::Stab | >| | | | memory to | ilizedSQPInt | >| | | | store | ernal | >| | | | history of | | >| | | | merit | | >| | | | function | | >| | | | values | | >+--------------+--------------+--------------+--------------+--------------+ >| min_step_siz | OT_REAL | 0.000 | The size | CasADi::Stab | >| e | | | (inf-norm) | ilizedSQPInt | >| | | | of the step | ernal | >| | | | size should | | >| | | | not become | | >| | | | smaller than | | >| | | | this. | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | CasADi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | CasADi::Stab | >| | | | uts) (eval_ | ilizedSQPInt | >| | | | f|eval_g|eva | ernal | >| | | | l_jac_g|eval | | >| | | | _grad_f|eval | | >| | | | _h|qp|dx) | | >+--------------+--------------+--------------+--------------+--------------+ >| muR0 | OT_REAL | 0.000 | Initial | CasADi::Stab | >| | | | choice of re | ilizedSQPInt | >| | | | gularization | ernal | >| | | | parameter | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | CasADi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| nu | OT_REAL | 1 | Parameter | CasADi::Stab | >| | | | for primal- | ilizedSQPInt | >| | | | dual | ernal | >| | | | augmented | | >| | | | Lagrangian. | | >+--------------+--------------+--------------+--------------+--------------+ >| parametric | OT_BOOLEAN | GenericType( | Deprecated | CasADi::NLPS | >| | | ) | option. | olverInterna | >| | | | Expect F, G, | l | >| | | | H, J to have | | >| | | | an | | >| | | | additional | | >| | | | input | | >| | | | argument | | >| | | | appended at | | >| | | | the end, | | >| | | | denoting | | >| | | | fixed | | >| | | | parameters. | | >+--------------+--------------+--------------+--------------+--------------+ >| phiWeight | OT_REAL | 0.000 | Weight used | CasADi::Stab | >| | | | in pseudo- | ilizedSQPInt | >| | | | filter. | ernal | >+--------------+--------------+--------------+--------------+--------------+ >| print_header | OT_BOOLEAN | true | Print the | CasADi::Stab | >| | | | header with | ilizedSQPInt | >| | | | problem | ernal | >| | | | statistics | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | CasADi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| regularize | OT_BOOLEAN | false | Automatic re | CasADi::Stab | >| | | | gularization | ilizedSQPInt | >| | | | of Lagrange | ernal | >| | | | Hessian. | | >+--------------+--------------+--------------+--------------+--------------+ >| stabilized_q | OT_STABILIZE | GenericType( | The | CasADi::Stab | >| p_solver | DQPSOLVER | ) | Stabilized | ilizedSQPInt | >| | | | QP solver to | ernal | >| | | | be used by | | >| | | | the SQP | | >| | | | method | | >+--------------+--------------+--------------+--------------+--------------+ >| stabilized_q | OT_DICTIONAR | GenericType( | Options to | CasADi::Stab | >| p_solver_opt | Y | ) | be passed to | ilizedSQPInt | >| ions | | | the | ernal | >| | | | Stabilized | | >| | | | QP solver | | >+--------------+--------------+--------------+--------------+--------------+ >| tau0 | OT_REAL | 0.010 | Initial | CasADi::Stab | >| | | | parameter | ilizedSQPInt | >| | | | for the | ernal | >| | | | merit | | >| | | | function | | >| | | | optimality | | >| | | | threshold. | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_du | OT_REAL | 0.000 | Stopping | CasADi::Stab | >| | | | criterion | ilizedSQPInt | >| | | | for dual inf | ernal | >| | | | easability | | >+--------------+--------------+--------------+--------------+--------------+ >| tol_pr | OT_REAL | 0.000 | Stopping | CasADi::Stab | >| | | | criterion | ilizedSQPInt | >| | | | for primal i | ernal | >| | | | nfeasibility | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | | >+--------------+--------------+--------------+--------------+--------------+ >| yEinitial | OT_STRING | "simple" | Initial | CasADi::Stab | >| | | | multiplier. | ilizedSQPInt | >| | | | Simple (all | ernal | >| | | | zero) or | | >| | | | least (LSQ). | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available monitors >+-------------+-------------------------------+ >| Id | Used in | >+=============+===============================+ >| dx | CasADi::StabilizedSQPInternal | >+-------------+-------------------------------+ >| eval_f | CasADi::StabilizedSQPInternal | >+-------------+-------------------------------+ >| eval_g | CasADi::StabilizedSQPInternal | >+-------------+-------------------------------+ >| eval_grad_f | CasADi::StabilizedSQPInternal | >+-------------+-------------------------------+ >| eval_h | CasADi::StabilizedSQPInternal | >+-------------+-------------------------------+ >| eval_jac_g | CasADi::StabilizedSQPInternal | >+-------------+-------------------------------+ >| inputs | CasADi::FunctionInternal | >+-------------+-------------------------------+ >| outputs | CasADi::FunctionInternal | >+-------------+-------------------------------+ >| qp | CasADi::StabilizedSQPInternal | >+-------------+-------------------------------+ > >>List of available stats >+---------------+-------------------------------+ >| Id | Used in | >+===============+===============================+ >| iter_count | CasADi::StabilizedSQPInternal | >+---------------+-------------------------------+ >| return_status | CasADi::StabilizedSQPInternal | >+---------------+-------------------------------+ > >Diagrams > >C++ includes: stabilized_sqp_method.hpp -} newtype StabilizedSQPMethod = StabilizedSQPMethod (ForeignPtr StabilizedSQPMethod') -- typeclass decl class StabilizedSQPMethodClass a where castStabilizedSQPMethod :: a -> StabilizedSQPMethod instance StabilizedSQPMethodClass StabilizedSQPMethod where castStabilizedSQPMethod = id -- baseclass instances instance SharedObjectClass StabilizedSQPMethod where castSharedObject (StabilizedSQPMethod x) = SharedObject (castForeignPtr x) instance PrintableObjectClass StabilizedSQPMethod where castPrintableObject (StabilizedSQPMethod x) = PrintableObject (castForeignPtr x) instance OptionsFunctionalityClass StabilizedSQPMethod where castOptionsFunctionality (StabilizedSQPMethod x) = OptionsFunctionality (castForeignPtr x) instance FunctionClass StabilizedSQPMethod where castFunction (StabilizedSQPMethod x) = Function (castForeignPtr x) instance IOInterfaceFunctionClass StabilizedSQPMethod where castIOInterfaceFunction (StabilizedSQPMethod x) = IOInterfaceFunction (castForeignPtr x) instance NLPSolverClass StabilizedSQPMethod where castNLPSolver (StabilizedSQPMethod x) = NLPSolver (castForeignPtr x) -- helper instances instance Marshal StabilizedSQPMethod (Ptr StabilizedSQPMethod') where marshal (StabilizedSQPMethod x) = return (unsafeForeignPtrToPtr x) marshalFree (StabilizedSQPMethod x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_CasADi__StabilizedSQPMethod" c_delete_CasADi__StabilizedSQPMethod :: FunPtr (Ptr StabilizedSQPMethod' -> IO ()) instance WrapReturn (Ptr StabilizedSQPMethod') StabilizedSQPMethod where wrapReturn = (fmap StabilizedSQPMethod) . (newForeignPtr c_delete_CasADi__StabilizedSQPMethod) -- raw decl data IOScheme' -- data decl {-| >[INTERNAL] 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 SharedObjectClass IOScheme where castSharedObject (IOScheme x) = SharedObject (castForeignPtr x) instance PrintableObjectClass IOScheme where castPrintableObject (IOScheme x) = PrintableObject (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)