{-# OPTIONS_GHC -Wall #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.SnoptInterface.Data where import Prelude hiding ( Functor ) import Foreign.Ptr ( Ptr, FunPtr ) import Foreign.ForeignPtr ( ForeignPtr, castForeignPtr, newForeignPtr, touchForeignPtr ) import Foreign.ForeignPtr.Unsafe ( unsafeForeignPtrToPtr ) import Casadi.Internal.Marshal ( Marshal(..) ) import Casadi.Internal.WrapReturn ( WrapReturn(..) ) import Casadi.Core.Data -- raw decl data SnoptSolver' -- data decl {-| >interface to SNOPT 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 > >>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 | >+==============+==============+==============+==============+==============+ >| _iprint | OT_INTEGER | 0 | | casadi::Snop | >| | | | | tInternal | >+--------------+--------------+--------------+--------------+--------------+ >| _isumm | OT_INTEGER | 6 | | casadi::Snop | >| | | | | tInternal | >+--------------+--------------+--------------+--------------+--------------+ >| _start | OT_STRING | "Cold" | (Cold|Warm) | casadi::Snop | >| | | | | tInternal | >+--------------+--------------+--------------+--------------+--------------+ >| 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 . | | >+--------------+--------------+--------------+--------------+--------------+ >| detect_linea | OT_BOOLEAN | true | Make an | casadi::Snop | >| r | | | effort to | tInternal | >| | | | treat linear | | >| | | | constraints | | >| | | | and linear | | >| | | | variables | | >| | | | specially. | | >+--------------+--------------+--------------+--------------+--------------+ >| expand | OT_BOOLEAN | false | Expand the | casadi::NLPS | >| | | | NLP function | olverInterna | >| | | | in terms of | l | >| | | | scalar | | >| | | | operations, | | >| | | | i.e. MX->SX | | >+--------------+--------------+--------------+--------------+--------------+ >| gather_stats | OT_BOOLEAN | false | Flag to | casadi::Func | >| | | | indicate | tionInternal | >| | | | whether | | >| | | | statistics | | >| | | | must be | | >| | | | gathered | | >+--------------+--------------+--------------+--------------+--------------+ >| grad_f | OT_FUNCTION | GenericType( | Function for | casadi::NLPS | >| | | ) | calculating | olverInterna | >| | | | the gradient | l | >| | | | of the | | >| | | | objective | | >| | | | (column, aut | | >| | | | ogenerated | | >| | | | by default) | | >+--------------+--------------+--------------+--------------+--------------+ >| grad_lag | OT_FUNCTION | GenericType( | Function for | casadi::NLPS | >| | | ) | calculating | olverInterna | >| | | | the gradient | l | >| | | | of the | | >| | | | Lagrangian ( | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| hess_lag | OT_FUNCTION | GenericType( | Function for | casadi::NLPS | >| | | ) | calculating | olverInterna | >| | | | the Hessian | l | >| | | | of the | | >| | | | Lagrangian ( | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| ignore_check | OT_BOOLEAN | false | If set to | casadi::NLPS | >| _vec | | | true, the | olverInterna | >| | | | input shape | l | >| | | | of F will | | >| | | | not be | | >| | | | checked. | | >+--------------+--------------+--------------+--------------+--------------+ >| inputs_check | OT_BOOLEAN | true | Throw | casadi::Func | >| | | | exceptions | tionInternal | >| | | | when the | | >| | | | numerical | | >| | | | values of | | >| | | | the inputs | | >| | | | don't make | | >| | | | sense | | >+--------------+--------------+--------------+--------------+--------------+ >| iteration_ca | OT_CALLBACK | GenericType( | A function | casadi::NLPS | >| llback | | ) | that will be | olverInterna | >| | | | called at | l | >| | | | each | | >| | | | iteration | | >| | | | with the | | >| | | | solver as | | >| | | | input. Check | | >| | | | documentatio | | >| | | | n of | | >| | | | Callback . | | >+--------------+--------------+--------------+--------------+--------------+ >| iteration_ca | OT_BOOLEAN | false | If set to | casadi::NLPS | >| llback_ignor | | | true, errors | olverInterna | >| e_errors | | | thrown by it | l | >| | | | eration_call | | >| | | | back will be | | >| | | | ignored. | | >+--------------+--------------+--------------+--------------+--------------+ >| iteration_ca | OT_INTEGER | 1 | Only call | casadi::NLPS | >| llback_step | | | the callback | olverInterna | >| | | | function | l | >| | | | every few | | >| | | | iterations. | | >+--------------+--------------+--------------+--------------+--------------+ >| jac_f | OT_FUNCTION | GenericType( | Function for | casadi::NLPS | >| | | ) | calculating | olverInterna | >| | | | the jacobian | l | >| | | | of the | | >| | | | objective | | >| | | | (sparse row, | | >| | | | autogenerate | | >| | | | d by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| jac_g | OT_FUNCTION | GenericType( | Function for | casadi::NLPS | >| | | ) | calculating | olverInterna | >| | | | the Jacobian | l | >| | | | of the | | >| | | | constraints | | >| | | | (autogenerat | | >| | | | ed by | | >| | | | default) | | >+--------------+--------------+--------------+--------------+--------------+ >| monitor | OT_STRINGVEC | GenericType( | Monitors to | casadi::Func | >| | TOR | ) | be activated | tionInternal | >| | | | (inputs|outp | casadi::Snop | >| | | | uts) (eval_ | tInternal | >| | | | nlp|setup_nl | | >| | | | p) | | >+--------------+--------------+--------------+--------------+--------------+ >| name | OT_STRING | "unnamed_sha | name of the | casadi::Opti | >| | | red_object" | object | onsFunctiona | >| | | | | lityNode | >+--------------+--------------+--------------+--------------+--------------+ >| print_time | OT_BOOLEAN | true | print | casadi::Snop | >| | | | information | tInternal | >| | | | about | | >| | | | execution | | >| | | | time | | >+--------------+--------------+--------------+--------------+--------------+ >| regularity_c | OT_BOOLEAN | true | Throw | casadi::Func | >| heck | | | exceptions | tionInternal | >| | | | when NaN or | | >| | | | Inf appears | | >| | | | during | | >| | | | evaluation | | >+--------------+--------------+--------------+--------------+--------------+ >| user_data | OT_VOIDPTR | GenericType( | A user- | casadi::Func | >| | | ) | defined | tionInternal | >| | | | field that | | >| | | | can be used | | >| | | | to identify | | >| | | | the function | | >| | | | or pass | | >| | | | additional | | >| | | | information | | >+--------------+--------------+--------------+--------------+--------------+ >| verbose | OT_BOOLEAN | false | Verbose | casadi::Func | >| | | | evaluation | tionInternal | >| | | | for | | >| | | | debugging | | >+--------------+--------------+--------------+--------------+--------------+ >| warn_initial | OT_BOOLEAN | false | Warn if the | casadi::NLPS | >| _bounds | | | initial | olverInterna | >| | | | guess does | l | >| | | | not satisfy | | >| | | | LBX and UBX | | >+--------------+--------------+--------------+--------------+--------------+ > >>List of available monitors >+-----------+--------------------------+ >| Id | Used in | >+===========+==========================+ >| eval_nlp | casadi::SnoptInternal | >+-----------+--------------------------+ >| inputs | casadi::FunctionInternal | >+-----------+--------------------------+ >| outputs | casadi::FunctionInternal | >+-----------+--------------------------+ >| setup_nlp | casadi::SnoptInternal | >+-----------+--------------------------+ > >>List of available stats >+----------------+-----------------------+ >| Id | Used in | >+================+=======================+ >| n_callback_fun | casadi::SnoptInternal | >+----------------+-----------------------+ >| n_eval_grad_f | casadi::SnoptInternal | >+----------------+-----------------------+ >| n_eval_jac_g | casadi::SnoptInternal | >+----------------+-----------------------+ >| return_status | casadi::SnoptInternal | >+----------------+-----------------------+ >| t_callback_fun | casadi::SnoptInternal | >+----------------+-----------------------+ >| t_eval_grad_f | casadi::SnoptInternal | >+----------------+-----------------------+ >| t_eval_jac_g | casadi::SnoptInternal | >+----------------+-----------------------+ >| t_mainloop | casadi::SnoptInternal | >+----------------+-----------------------+ > >Diagrams > >C++ includes: snopt_solver.hpp -} newtype SnoptSolver = SnoptSolver (ForeignPtr SnoptSolver') -- typeclass decl class SnoptSolverClass a where castSnoptSolver :: a -> SnoptSolver instance SnoptSolverClass SnoptSolver where castSnoptSolver = id -- baseclass instances instance NLPSolverClass SnoptSolver where castNLPSolver (SnoptSolver x) = NLPSolver (castForeignPtr x) -- helper instances instance Marshal SnoptSolver (Ptr SnoptSolver') where marshal (SnoptSolver x) = return (unsafeForeignPtrToPtr x) marshalFree (SnoptSolver x) _ = touchForeignPtr x foreign import ccall unsafe "&delete_casadi__SnoptSolver" c_delete_casadi__SnoptSolver :: FunPtr (Ptr SnoptSolver' -> IO ()) instance WrapReturn (Ptr SnoptSolver') SnoptSolver where wrapReturn = (fmap SnoptSolver) . (newForeignPtr c_delete_casadi__SnoptSolver)