{-# OPTIONS_GHC -Wall #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# Language ForeignFunctionInterface #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.Wrappers.Classes.NLPSolver ( NLPSolver, NLPSolverClass(..), nlpSolver, nlpSolver_checkNode, nlpSolver_getReportConstraints, nlpSolver_gradF, nlpSolver_hessLag, nlpSolver_jacG, nlpSolver_joinFG, nlpSolver_nlp, nlpSolver_reportConstraints', nlpSolver_setQPOptions, ) where import Prelude hiding ( Functor ) import Data.Vector ( Vector ) import Foreign.C.Types import Foreign.Ptr ( Ptr ) import Foreign.ForeignPtr ( newForeignPtr ) import System.IO.Unsafe ( unsafePerformIO ) -- for show instances import Casadi.Wrappers.Classes.PrintableObject import Casadi.Wrappers.CToolsInstances ( ) import Casadi.Wrappers.Data import Casadi.Wrappers.Enums import Casadi.MarshalTypes ( CppVec, StdString' ) -- StdOstream' import Casadi.Marshal ( Marshal(..), withMarshal ) import Casadi.WrapReturn ( WrapReturn(..) ) instance Show NLPSolver where show = unsafePerformIO . printableObject_getDescription -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__checkNode" c_CasADi__NLPSolver__checkNode :: Ptr NLPSolver' -> IO CInt casADi__NLPSolver__checkNode :: NLPSolver -> IO Bool casADi__NLPSolver__checkNode x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__checkNode x0' >>= wrapReturn -- classy wrapper {-| >Check if the node is pointing to the right type of object. -} nlpSolver_checkNode :: NLPSolverClass a => a -> IO Bool nlpSolver_checkNode x = casADi__NLPSolver__checkNode (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__reportConstraints_TIC" c_CasADi__NLPSolver__reportConstraints_TIC :: Ptr NLPSolver' -> IO () casADi__NLPSolver__reportConstraints' :: NLPSolver -> IO () casADi__NLPSolver__reportConstraints' x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__reportConstraints_TIC x0' >>= wrapReturn -- classy wrapper nlpSolver_reportConstraints' :: NLPSolverClass a => a -> IO () nlpSolver_reportConstraints' x = casADi__NLPSolver__reportConstraints' (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__getReportConstraints" c_CasADi__NLPSolver__getReportConstraints :: Ptr NLPSolver' -> IO (Ptr StdString') casADi__NLPSolver__getReportConstraints :: NLPSolver -> IO String casADi__NLPSolver__getReportConstraints x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__getReportConstraints x0' >>= wrapReturn -- classy wrapper nlpSolver_getReportConstraints :: NLPSolverClass a => a -> IO String nlpSolver_getReportConstraints x = casADi__NLPSolver__getReportConstraints (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__setQPOptions" c_CasADi__NLPSolver__setQPOptions :: Ptr NLPSolver' -> IO () casADi__NLPSolver__setQPOptions :: NLPSolver -> IO () casADi__NLPSolver__setQPOptions x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__setQPOptions x0' >>= wrapReturn -- classy wrapper {-| >Set options that make the NLP solver more suitable for solving QPs. -} nlpSolver_setQPOptions :: NLPSolverClass a => a -> IO () nlpSolver_setQPOptions x = casADi__NLPSolver__setQPOptions (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__nlp" c_CasADi__NLPSolver__nlp :: Ptr NLPSolver' -> IO (Ptr Function') casADi__NLPSolver__nlp :: NLPSolver -> IO Function casADi__NLPSolver__nlp x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__nlp x0' >>= wrapReturn -- classy wrapper {-| >Access the NLP. > >>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) . | >+------------------------+------------------------+------------------------+ -} nlpSolver_nlp :: NLPSolverClass a => a -> IO Function nlpSolver_nlp x = casADi__NLPSolver__nlp (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__gradF" c_CasADi__NLPSolver__gradF :: Ptr NLPSolver' -> IO (Ptr Function') casADi__NLPSolver__gradF :: NLPSolver -> IO Function casADi__NLPSolver__gradF x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__gradF x0' >>= wrapReturn -- classy wrapper {-| >Access the objective gradient function>Input scheme: CasADi::GradFInput >(GRADF_NUM_IN = 3) [gradFIn] +-----------+-------+---------------------+ | >Full name | Short | Description | >+===========+=======+=====================+ | GRADF_X | x | Decision >variable . | +-----------+-------+---------------------+ | GRADF_P | p >| Fixed parameter . | +-----------+-------+---------------------+ -} nlpSolver_gradF :: NLPSolverClass a => a -> IO Function nlpSolver_gradF x = casADi__NLPSolver__gradF (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__jacG" c_CasADi__NLPSolver__jacG :: Ptr NLPSolver' -> IO (Ptr Function') casADi__NLPSolver__jacG :: NLPSolver -> IO Function casADi__NLPSolver__jacG x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__jacG x0' >>= wrapReturn -- classy wrapper {-| >Access the Jacobian of the constraint function. > >>Input scheme: CasADi::HessLagInput (HESSLAG_NUM_IN = 5) [hessLagIn] >+------------------------+------------------------+------------------------+ >| Full name | Short | Description | >+========================+========================+========================+ >| HESSLAG_X | x | Decision variable . | >+------------------------+------------------------+------------------------+ >| HESSLAG_P | p | Fixed parameter . | >+------------------------+------------------------+------------------------+ >| HESSLAG_LAM_F | lam_f | Multiplier for f. Just | >| | | a scalar factor for | >| | | the objective that the | >| | | NLP solver might use | >| | | to scale the | >| | | objective. . | >+------------------------+------------------------+------------------------+ >| HESSLAG_LAM_G | lam_g | Multiplier for g . | >+------------------------+------------------------+------------------------+ > >>Output scheme: CasADi::HessLagOutput (HESSLAG_NUM_OUT = 6) [hessLagOut] >+----------------+--------+------------------------------------------------+ >| Full name | Short | Description | >+================+========+================================================+ >| HESSLAG_HESS | hess | Hessian of the Lagrangian . | >+----------------+--------+------------------------------------------------+ >| HESSLAG_F | f | Objective function . | >+----------------+--------+------------------------------------------------+ >| HESSLAG_G | g | Constraint function . | >+----------------+--------+------------------------------------------------+ >| HESSLAG_GRAD_X | grad_x | Gradient of the Lagrangian with respect to x . | >+----------------+--------+------------------------------------------------+ >| HESSLAG_GRAD_P | grad_p | Gradient of the Lagrangian with respect to p . | >+----------------+--------+------------------------------------------------+ -} nlpSolver_jacG :: NLPSolverClass a => a -> IO Function nlpSolver_jacG x = casADi__NLPSolver__jacG (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__hessLag" c_CasADi__NLPSolver__hessLag :: Ptr NLPSolver' -> IO (Ptr Function') casADi__NLPSolver__hessLag :: NLPSolver -> IO Function casADi__NLPSolver__hessLag x0 = withMarshal x0 $ \x0' -> c_CasADi__NLPSolver__hessLag x0' >>= wrapReturn -- classy wrapper {-| >Access the Hessian of the Lagrangian function. > >>Input scheme: CasADi::JacGInput (JACG_NUM_IN = 3) [jacGIn] >+-----------+-------+---------------------+ >| Full name | Short | Description | >+===========+=======+=====================+ >| JACG_X | x | Decision variable . | >+-----------+-------+---------------------+ >| JACG_P | p | Fixed parameter . | >+-----------+-------+---------------------+ > >>Output scheme: CasADi::JacGOutput (JACG_NUM_OUT = 4) [jacGOut] >+-----------+-------+-------------------------------+ >| Full name | Short | Description | >+===========+=======+===============================+ >| JACG_JAC | jac | Jacobian of the constraints . | >+-----------+-------+-------------------------------+ >| JACG_F | f | Objective function . | >+-----------+-------+-------------------------------+ >| JACG_G | g | Constraint function . | >+-----------+-------+-------------------------------+ -} nlpSolver_hessLag :: NLPSolverClass a => a -> IO Function nlpSolver_hessLag x = casADi__NLPSolver__hessLag (castNLPSolver x) -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__joinFG" c_CasADi__NLPSolver__joinFG :: Ptr Function' -> Ptr Function' -> IO (Ptr Function') casADi__NLPSolver__joinFG :: Function -> Function -> IO Function casADi__NLPSolver__joinFG x0 x1 = withMarshal x0 $ \x0' -> withMarshal x1 $ \x1' -> c_CasADi__NLPSolver__joinFG x0' x1' >>= wrapReturn -- classy wrapper nlpSolver_joinFG :: Function -> Function -> IO Function nlpSolver_joinFG = casADi__NLPSolver__joinFG -- direct wrapper foreign import ccall unsafe "CasADi__NLPSolver__NLPSolver" c_CasADi__NLPSolver__NLPSolver :: IO (Ptr NLPSolver') casADi__NLPSolver__NLPSolver :: IO NLPSolver casADi__NLPSolver__NLPSolver = c_CasADi__NLPSolver__NLPSolver >>= wrapReturn -- classy wrapper {-| >Default constructor. -} nlpSolver :: IO NLPSolver nlpSolver = casADi__NLPSolver__NLPSolver