{-# OPTIONS_GHC -Wall #-} {-# Language FlexibleInstances #-} {-# Language MultiParamTypeClasses #-} module Casadi.IpoptInterface.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 IpoptSolver' -- data decl {-| >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 | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | >| | | | 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) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | 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) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | mumps | Linear | casadi::Ipop | >| r | | | solver used | tInternal | >| | | | for step com | | >| | | | putations. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| linear_syste | OT_STRING | none | 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 | 2 | 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 | no | 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 | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_buffer_ | OT_INTEGER | 4096 | Number of | casadi::Ipop | >| lpage | | | scalars per | tInternal | >| | | | MA77 buffer | | >| | | | page (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_buffer_ | OT_INTEGER | 1600 | Number of | casadi::Ipop | >| npage | | | pages that | tInternal | >| | | | make up MA77 | | >| | | | buffer (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_file_si | OT_INTEGER | 2097152 | Target size | casadi::Ipop | >| ze | | | of each | tInternal | >| | | | temporary | | >| | | | file for | | >| | | | MA77, | | >| | | | scalars per | | >| | | | type (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_maxstor | OT_INTEGER | 0 | Maximum | casadi::Ipop | >| e | | | storage size | tInternal | >| | | | for MA77 in- | | >| | | | core mode | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_nemin | OT_INTEGER | 8 | Node | casadi::Ipop | >| | | | Amalgamation | tInternal | >| | | | parameter | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_order | OT_STRING | amd | Controls | casadi::Ipop | >| | | | type of | tInternal | >| | | | ordering | | >| | | | used by | | >| | | | HSL_MA77 | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_print_l | OT_INTEGER | -1 | Debug | casadi::Ipop | >| evel | | | printing | tInternal | >| | | | level for | | >| | | | the linear | | >| | | | solver MA77 | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_small | OT_REAL | 0.000 | Zero Pivot | casadi::Ipop | >| | | | Threshold | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_static | OT_REAL | 0 | Static | casadi::Ipop | >| | | | Pivoting | tInternal | >| | | | Threshold | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_u | OT_REAL | 0.000 | Pivoting | casadi::Ipop | >| | | | Threshold | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma77_umax | OT_REAL | 0.000 | Maximum | casadi::Ipop | >| | | | Pivoting | tInternal | >| | | | Threshold | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_nemin | OT_INTEGER | 32 | Node | casadi::Ipop | >| | | | Amalgamation | tInternal | >| | | | parameter | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_order | OT_STRING | amd | Controls | casadi::Ipop | >| | | | type of | tInternal | >| | | | ordering | | >| | | | used by | | >| | | | HSL_MA86 | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_print_l | OT_INTEGER | -1 | Debug | casadi::Ipop | >| evel | | | printing | tInternal | >| | | | level for | | >| | | | the linear | | >| | | | solver MA86 | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma86_scaling | OT_STRING | mc64 | Controls | casadi::Ipop | >| | | | scaling of | tInternal | >| | | | matrix (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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 | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_nemin | OT_INTEGER | 8 | Node | casadi::Ipop | >| | | | Amalgamation | tInternal | >| | | | parameter | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_order | OT_STRING | auto | Controls | casadi::Ipop | >| | | | type of | tInternal | >| | | | ordering | | >| | | | used by | | >| | | | HSL_MA97 | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_print_l | OT_INTEGER | 0 | Debug | casadi::Ipop | >| evel | | | printing | tInternal | >| | | | level for | | >| | | | the linear | | >| | | | solver MA97 | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_scaling | OT_STRING | dynamic | Specifies | casadi::Ipop | >| | | | strategy for | tInternal | >| | | | scaling in | | >| | | | HSL_MA97 | | >| | | | linear | | >| | | | solver (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_scaling | OT_STRING | mc64 | First | casadi::Ipop | >| 1 | | | scaling. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_scaling | OT_STRING | mc64 | Second | casadi::Ipop | >| 2 | | | scaling. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_scaling | OT_STRING | mc64 | Third | casadi::Ipop | >| 3 | | | scaling. | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_small | OT_REAL | 0.000 | Zero Pivot | casadi::Ipop | >| | | | Threshold | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_solve_b | OT_STRING | no | Controls if | casadi::Ipop | >| las3 | | | blas2 or | tInternal | >| | | | blas3 | | >| | | | routines are | | >| | | | used for | | >| | | | solve (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_switch1 | OT_STRING | od_hd_reuse | First | casadi::Ipop | >| | | | switch, | tInternal | >| | | | determine | | >| | | | when ma97_sc | | >| | | | aling1 is | | >| | | | enabled. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_switch2 | OT_STRING | never | Second | casadi::Ipop | >| | | | switch, | tInternal | >| | | | determine | | >| | | | when ma97_sc | | >| | | | aling2 is | | >| | | | enabled. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_switch3 | OT_STRING | never | Third | casadi::Ipop | >| | | | switch, | tInternal | >| | | | determine | | >| | | | when ma97_sc | | >| | | | aling3 is | | >| | | | enabled. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_u | OT_REAL | 0.000 | Pivoting | casadi::Ipop | >| | | | Threshold | tInternal | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| ma97_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 | 0 | 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 | ipopt.opt | File name of | casadi::Ipop | >| name | | | options | tInternal | >| | | | file. (see | | >| | | | IPOPT docume | | >| | | | ntation) | | >+--------------+--------------+--------------+--------------+--------------+ >| output_file | OT_STRING | | File name of | casadi::Ipop | >| | | | desired | tInternal | >| | | | output file | | >| | | | (leave unset | | >| | | | for no file | | >| | | | output). | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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_freque | OT_INTEGER | 1 | Determines | casadi::Ipop | >| ncy_iter | | | at which | tInternal | >| | | | iteration | | >| | | | frequency | | >| | | | the | | >| | | | summarizing | | >| | | | iteration | | >| | | | output line | | >| | | | should be | | >| | | | printed. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| print_freque | OT_REAL | 0 | Determines | casadi::Ipop | >| ncy_time | | | at which | tInternal | >| | | | time | | >| | | | frequency | | >| | | | the | | >| | | | summarizing | | >| | | | iteration | | >| | | | output line | | >| | | | should be | | >| | | | printed. | | >| | | | (see IPOPT d | | >| | | | ocumentation | | >| | | | ) | | >+--------------+--------------+--------------+--------------+--------------+ >| 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_iterati | OT_STRING | no | Switches to | casadi::Ipop | >| ve | | | iterative | tInternal | >| | | | solver in | | >| | | | WSMP. (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 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)