nlp.c
Go to the documentation of this file.
29 /*---+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8----+----9----+----0----+----1----+----2*/ 52 /* to get value of parameter "nlp/solver" and nlpis array and to get access to set->lp for releasing a variable */ 59 #define EVENTHDLR_NAME "nlpEventHdlr" /**< name of NLP event handler that catches variable events */ 60 #define EVENTHDLR_DESC "handles all events necessary for maintaining NLP data" /**< description of NLP event handler */ 164 SCIP_ALLOC( BMSreallocBlockMemoryArray(tree->blkmem, &tree->vars, tree->nvars, tree->nvars + nvars) ); 202 /** searches the variables array of an expression tree for a variable and returns its position, or -1 if not found 222 /** removes fixed variables from an expression tree, so that at exit all variables are active */ 226 SCIP_Bool* changed, /**< buffer to store whether the tree was changed, i.e., whether there was a fixed variable */ 227 int* varpos, /**< array of length at least tree->nvars to store new indices of previously existing variables in expression tree, or -1 if variable was removed; set to NULL if not of interest */ 228 int* newvarsstart /**< buffer to store index in tree->vars array where new variables begin, or NULL if not of interest */ 255 /* create hash map from variable to indices in tree->vars and check if there is a non-fixed variable */ 284 /* construct for each nonactive variable an expression that replaces this variable in the tree */ 324 SCIP_CALL( SCIPexprCreateLinear(tree->blkmem, &replaceexprs[i], 1, &replaceexprs[i], &scalar, constant) ); 336 /* var is now multi-aggregated, thus replace by scalar * (multaggrconst + sum_j multaggrscalar_j*multaggrvar_j) + constant */ 340 SCIP_ALLOC( BMSallocBlockMemoryArray(tree->blkmem, &children, SCIPvarGetMultaggrNVars(var)) ); /*lint !e666 */ 341 SCIP_ALLOC( BMSallocBlockMemoryArray(tree->blkmem, &coefs, SCIPvarGetMultaggrNVars(var)) ); /*lint !e666 */ 345 * turn each variable in SCIPvarGetMultaggrVars(var) into an active or multi-aggregated one and add corresponding term to summands */ 394 SCIP_CALL( SCIPexprCreateLinear(tree->blkmem, &replaceexprs[i], nchildren, children, coefs, constant) ); 421 assert(i < nvarsold || SCIPvarIsActive((SCIP_VAR*)tree->vars[i]) || SCIPvarGetStatus((SCIP_VAR*)tree->vars[i]) == SCIP_VARSTATUS_MULTAGGR); 460 SCIP_ALLOC( BMSreallocBlockMemoryArray(tree->blkmem, &tree->vars, tree->nvars, tree->nvars - offset) ); 472 /* if there are still fixed variables left, then this are newly added multi-aggregated variables 473 * it is then save to call this function recursively, since the original active variables should not be moved, 532 SCIP_CALL( SCIPnlpiChgLinearCoefs(nlp->solver, nlp->problem, nlrow->nlpiindex, 1, &idx, &coef) ); 545 SCIP_QUADELEM quadelem, /**< new element (variable indices and new values), quadelem.coef == 0 if it was deleted */ 659 assert(SCIPvarIsActive(var)); /* at this point, there should be only active variables in the row */ 665 SCIP_CALL( SCIPnlpiChgExprtree(nlp->solver, nlp->problem, nlrow->nlpiindex, nlinidxs, nlrow->exprtree) ); 714 SCIP_CALL( SCIPnlpiChgNonlinCoef(nlp->solver, nlp->problem, nlrow->nlpiindex, paramidx, SCIPexprtreeGetParamVals(nlrow->exprtree)[paramidx]) ); 727 SCIP_CALL( SCIPnlpiChgNonlinCoef(nlp->solver, nlp->problem, nlrow->nlpiindex, i, paramvals[i]) ); 838 /** searches linear variable in nonlinear row, returns position in linvars vector or -1 if not found */ 854 if( !SCIPsortedvecFindPtr((void**)nlrow->linvars, SCIPvarComp, (void*)var, nlrow->nlinvars, &pos) ) 860 /** moves a coefficient in a nonlinear row to a different place, and updates all corresponding data structures */ 976 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, SCIPvarGetMultaggrVars(var)[j], SCIPvarGetMultaggrScalars(var)[j] * coef, TRUE) ); 1026 /* move last coefficient to position of empty slot (should set sorted flag to FALSE, if not last variable was deleted) */ 1066 /** sets up the variable hash for quadratic variables, if the number of variables exceeds some given threshold */ 1081 SCIP_CALL( SCIPhashmapCreate(&nlrow->quadvarshash, blkmem, SCIPcalcHashtableSize(5 * nlrow->nquadvars)) ); 1086 SCIP_CALL( SCIPhashmapInsert(nlrow->quadvarshash, (void*)nlrow->quadvars[i], (void*)(size_t)i) ); 1111 /** searches quadratic elements in nonlinear row, returns position of given index pair in quadelems array or -1 if not found */ 1134 /** moves a quadratic element in a nonlinear row to a different place, and updates all corresponding data structures */ 1194 SCIPdebugMessage("added quadratic element %g * <%s> * <%s> at position %d to nonlinear row <%s>\n", 1195 elem.coef, SCIPvarGetName(nlrow->quadvars[elem.idx1]), SCIPvarGetName(nlrow->quadvars[elem.idx2]), pos, nlrow->name); 1216 SCIPdebugMessage("delete quad element (%d,%d) at pos %d\n", nlrow->quadelems[pos].idx1, nlrow->quadelems[pos].idx2, pos); 1220 /* move last coefficient to position of empty slot (should set sorted flag to FALSE, if not last element was deleted) */ 1246 SCIPdebugMessage("change quad element (%d,%d) at pos %d to %g\n", nlrow->quadelems[pos].idx1, nlrow->quadelems[pos].idx2, pos, coef); 1286 SCIPintervalSetBounds(&bounds, SCIPvarGetLbLocal(nlrow->linvars[i]), SCIPvarGetUbLocal(nlrow->linvars[i])); 1299 SCIPintervalSetBounds(&bounds, SCIPvarGetLbLocal(nlrow->quadvars[idx1]), SCIPvarGetUbLocal(nlrow->quadvars[idx1])); 1312 SCIPintervalSetBounds(&tmp, SCIPvarGetLbLocal(nlrow->quadvars[nlrow->quadelems[i].idx2]), SCIPvarGetUbLocal(nlrow->quadvars[nlrow->quadelems[i].idx2])); 1336 SCIPintervalSetBounds(&varvals[i], SCIPvarGetLbLocal(SCIPexprtreeGetVars(nlrow->exprtree)[i]), SCIPvarGetUbLocal(SCIPexprtreeGetVars(nlrow->exprtree)[i])); 1353 /** makes sure that there is no fixed variable at position pos of the linear part of a nonlinear row 1382 SCIP_CALL( SCIPvarGetProbvarSum( &nlrow->linvars[pos], set, &nlrow->lincoefs[pos], &nlrow->constant) ); 1409 SCIP_CALL( nlrowLinearCoefChanged(nlrow, set, stat, nlrow->linvars[pos], nlrow->lincoefs[pos], nlp) ); 1431 SCIP_CALL( SCIPnlrowEnsureLinearSize(nlrow, blkmem, set, nlrow->nlinvars + SCIPvarGetMultaggrNVars(var)) ); 1434 SCIP_CALL( nlrowAddLinearCoef(nlrow, blkmem, set, stat, nlp, SCIPvarGetMultaggrVars(var)[i], coef * SCIPvarGetMultaggrScalars(var)[i]) ); 1481 /** removes fixed quadratic variables of a nonlinear row by replacing them with the corresponding constant or disaggregated terms */ 1528 if( SCIPvarIsActive(nlrow->quadvars[elem.idx1]) && SCIPvarIsActive(nlrow->quadvars[elem.idx2]) ) 1542 i, elem.coef, SCIPvarGetName(nlrow->quadvars[elem.idx1]), SCIPvarGetName(nlrow->quadvars[elem.idx2])); 1544 /* if one of the variable is not active, we remove the element and insert new disaggregated ones */ 1575 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, var2, elem.coef * constant1 * coef2, TRUE) ); 1592 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, var1, elem.coef * coef1 * constant2, TRUE) ); 1613 * elem.coef * x^2 -> elem.coef * (coef1 * (multaggrconstant + sum_i multaggrscalar_i*multaggrvar_i) + constant1)^2 1615 * 2 * (coef1 * multaggrconstant + constant1) * coef1 * (sum_j multaggrscalar_j*multaggrvar_j) + 1633 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, SCIPvarGetMultaggrVars(var1)[j], 1634 2.0 * elem.coef * (coef1 * SCIPvarGetMultaggrConstant(var1) + constant1) * coef1 * SCIPvarGetMultaggrScalars(var1)[j], TRUE) ); 1652 /* add quadratic elements elem.coef * coef1^2 * (sum_{j,k} multaggrscalar_j*multaggrscalar_k*multaggrvar_j*multaggrvar_k) */ 1660 newelem.coef = 2 * elem.coef * coef1 * coef1 * SCIPvarGetMultaggrScalars(var1)[j] * SCIPvarGetMultaggrScalars(var1)[k]; 1667 newelem.coef = elem.coef * coef1 * coef1 * SCIPvarGetMultaggrScalars(var1)[j] * SCIPvarGetMultaggrScalars(var1)[j]; 1704 /* the first variable is multi-aggregated, add a constant and sequences of linear and quadratic terms: 1705 * elem.coef * x * y -> elem.coef * (coef1 * (multaggrconstant + sum_i multaggrscalar_i*multaggrvar_i) + constant1) * (coef2 * var2 + constant2) 1722 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, var2, elem.coef * (coef1 * SCIPvarGetMultaggrConstant(var1) + constant1) * coef2, TRUE) ); 1727 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, SCIPvarGetMultaggrVars(var1)[j], elem.coef * coef1 * SCIPvarGetMultaggrScalars(var1)[j] * constant2, TRUE) ); 1741 /* add quadratic elements elem.coef * coef1 * (sum_j multaggrscalar_j*multaggrvar_j) * coef2 * var2 */ 1781 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, var1, elem.coef * coef1 * constant2, TRUE) ); 1782 SCIP_CALL( nlrowAddToLinearCoef(nlrow, blkmem, set, stat, nlp, var2, elem.coef * coef2 * constant1, TRUE) ); 1860 /* it can have happened that a new quadratic variable was added that is not active (when multiplying two multi-aggregations) 1861 * in this case, the variable was only temporarily used and should not be used anymore (this is asserted in the next for-loop below), 1881 assert(nlrow->quadelems[i].idx1 <= nlrow->quadelems[i].idx2); /* the way we shrink the quadvars array, variables should stay in the same relative position to each other */ 1899 SCIP_CALL( SCIPhashmapSetImage(nlrow->quadvarshash, (void*)nlrow->quadvars[i], (void*)(size_t)newpos[i]) ); 1935 if( SCIPexprtreeGetNVars(nlrow->exprtree) == 0 && SCIPexprtreeGetNParams(nlrow->exprtree) == 0 ) 1972 /* search for variable in quadratic part and remove all fixed quadratic variables if existing */ 1979 /* search for variable in non-quadratic part and remove all fixed variables in expression tree if existing */ 2007 SCIP_QUADELEM* quadelems, /**< elements of quadratic term matrix, or NULL if nquadelems == 0 */ 2096 SCIP_ALLOC( BMSduplicateBlockMemoryArray(blkmem, &(*nlrow)->quadelems, quadelems, nquadelems) ); 2157 sourcenlrow->nquadvars, sourcenlrow->quadvars, sourcenlrow->nquadelems, sourcenlrow->quadelems, 2306 SCIPmessageFPrintInfo(messagehdlr, file, "%+.15g<%s> ", nlrow->lincoefs[i], SCIPvarGetName(nlrow->linvars[i])); 2315 SCIPmessageFPrintInfo(messagehdlr, file, "%+.15gsqr(<%s>) ", nlrow->quadelems[i].coef, SCIPvarGetName(nlrow->quadvars[nlrow->quadelems[i].idx1])); 2317 SCIPmessageFPrintInfo(messagehdlr, file, "%+.15g<%s><%s> ", nlrow->quadelems[i].coef, SCIPvarGetName(nlrow->quadvars[nlrow->quadelems[i].idx1]), SCIPvarGetName(nlrow->quadvars[nlrow->quadelems[i].idx2])); 2357 SCIPdebugMessage("release nonlinear row <%s> with nuses=%d\n", (*nlrow)->name, (*nlrow)->nuses); 2385 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlrow->linvars, nlrow->linvarssize, newsize) ); 2386 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlrow->lincoefs, nlrow->linvarssize, newsize) ); 2429 SCIP_CALL( SCIPnlrowAddLinearCoef(nlrow, blkmem, set, stat, nlp, SCIPvarGetMultaggrVars(var)[i], SCIPvarGetMultaggrScalars(var)[i] * val) ); 2456 /* if the row is in the NLP already, we can only have active variables, so var should also be active; in non-debug mode, one gets an error below */ 2463 SCIPerrorMessage("coefficient for variable <%s> doesn't exist in nonlinear row <%s>\n", SCIPvarGetName(var), nlrow->name); 2529 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlrow->quadvars, nlrow->quadvarssize, newsize) ); 2565 SCIP_CALL( SCIPhashmapInsert(nlrow->quadvarshash, (void*)var, (void*)(size_t)(nlrow->nquadvars-1)) ); 2588 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlrow->quadelems, nlrow->quadelemssize, newsize) ); 2634 SCIPerrorMessage("coefficient for index pair (idx1, idx2) doesn't exist in nonlinear row <%s>\n", idx1, idx2, nlrow->name); 2753 SCIP_CALL( SCIPexprtreeSetParams(nlrow->exprtree, SCIPexprtreeGetNParams(nlrow->exprtree), paramvals) ); 2821 /** removes (or substitutes) all fixed, negated, aggregated, multi-aggregated variables from the linear, quadratic, and non-quadratic terms of a nonlinear row */ 2941 /** gives the feasibility of a nonlinear row in the current NLP solution: negative value means infeasibility */ 3042 /** returns the pseudo feasibility of a nonlinear row in the current pseudo solution: negative value means infeasibility */ 3297 pos = SCIPhashmapExists(nlrow->quadvarshash, var) ? (int)(size_t)SCIPhashmapGetImage(nlrow->quadvarshash, var) : -1; 3334 int* nquadvars, /**< buffer to store number of variables in quadratic term, or NULL if not of interest */ 3335 SCIP_VAR*** quadvars, /**< buffer to store pointer to array of variables in quadratic term, or NULL if not of interest */ 3336 int* nquadelems, /**< buffer to store number of entries in quadratic term, or NULL if not of interest */ 3337 SCIP_QUADELEM** quadelems /**< buffer to store pointer to array of entries in quadratic term, or NULL if not of interest */ 3413 * for a ranged constraint, the dual value is positive if the right hand side is active and negative if the left hand side is active 3446 /* if we have a feasible NLP solution and it satisfies the modified row, then it is still feasible 3447 * if the NLP was globally or locally infeasible or unbounded, then this may not be the case anymore 3528 /* if we have a feasible NLP solution and it satisfies the new solution, then it is still feasible 3553 /** moves a nonlinear row to a different place, and updates all corresponding data structures */ 3664 /* if we have a feasible NLP solution and it satisfies the new bounds, then it is still feasible 3665 * if the NLP was globally or locally infeasible and we tightened a bound, then it stays that way 3722 /* if variable not in NLPI yet, then we only need to remember to update the objective after variable additions were flushed */ 3739 /* if we had a solution and it was locally (or globally) optimal, then now we can only be sure that it is still feasible */ 3816 nlp->eventhdlr, (SCIP_EVENTDATA*)nlp, NULL) ); /* @todo should store event filter position in nlp? */ 3895 /* use nlrowSearchLinearCoef only if already sorted, since otherwise we may change the solving process slightly */ 3944 /** notifies NLP that a variable was fixed, so it is removed from objective, all rows, and the NLP variables */ 3983 SCIP_QUADELEM** quadelems, /**< buffer to store pointer to quadratic elements w.r.t. NLPI indices */ 4009 assert(SCIPvarIsActive(var)); /* at this point, there should be only active variables in the row */ 4034 assert(SCIPvarIsActive(var)); /* at this point, there should be only active variables in the row */ 4037 quadvarsidx[i] = nlp->varmap_nlp2nlpi[(size_t) (void*) SCIPhashmapGetImage(nlp->varhash, var)]; 4079 assert(SCIPvarIsActive(var)); /* at this point, there should be only active variables in the row */ 4082 (*nlinidxs)[i] = nlp->varmap_nlp2nlpi[(size_t) (void*) SCIPhashmapGetImage(nlp->varhash, var)]; 4110 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlp->varmap_nlpi2nlp, nlp->sizevars_solver, newsize) ); 4138 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlp->nlrowmap_nlpi2nlp, nlp->sizenlrows_solver, newsize) ); 4200 assert(rowset[j] <= j); /* we assume that the NLP solver did not move a row behind its previous position!! */ 4239 * assumes that there are no pending row deletions (nlpFlushNlRowDeletions should be called first) 4293 assert(colset[i] <= i); /* we assume that the NLP solver did not move a variable behind its previous position!! */ 4334 * assumes that there are no pending variable additions or deletions (nlpFlushVarDeletions and nlpFlushVarAdditions should be called first) */ 4376 SCIP_CALL( nlpEnsureNlRowsSolverSize(nlp, blkmem, set, nlp->nnlrows_solver + nlp->nunflushednlrowadd) ); 4487 * may set nlp->objflushed to FALSE if a variable with nonzero obj.coefficient is added to the NLPI problem */ 4519 SCIP_CALL( nlpEnsureVarsSolverSize(nlp, blkmem, set, nlp->nvars_solver + nlp->nunflushedvaradd) ); 4546 /* if the new variable has a nonzero objective coefficient, then the objective need to be updated */ 4574 * assumes that there are no unflushed variable additions or deletions (nlpFlushVarDeletions and nlpFlushVarAdditions should be called first) 4686 SCIP_CALL( SCIPnlpiSetInitialGuess(nlp->solver, nlp->problem, initialguess_solver, NULL, NULL, NULL) ); 4719 SCIP_CALL( SCIPnlpiGetSolution(nlp->solver, nlp->problem, &primalvals, &nlrowdualvals, &varlbdualvals, &varubdualvals) ); 4721 assert((varlbdualvals != NULL) == (varubdualvals != NULL)); /* if there are duals for one bound, then there should also be duals for the other bound */ 4728 SCIP_CALL( SCIPvarSetNLPSol(nlp->vars[i], set, primalvals[nlp->varmap_nlp2nlpi[i]]) ); /*lint !e613 */ 4740 SCIP_CALL( SCIPvarSetNLPSol(nlp->vars[i], set, primalvals[nlp->varmap_nlp2nlpi[i]]) ); /*lint !e613 */ 4741 nlp->primalsolobjval += SCIPvarGetObj(nlp->vars[i]) * primalvals[nlp->varmap_nlp2nlpi[i]]; /*lint !e613 */ 4748 assert(nlp->nlrows[i]->nlpiindex >= 0); /* NLP was flushed before solve, so all nlrows should be in there */ 4750 nlp->nlrows[i]->dualsol = nlrowdualvals != NULL ? nlrowdualvals[nlp->nlrows[i]->nlpiindex] : 0.0; 4752 /* SCIPdebugMessage("dual of nlrow <%s> = %g\n", nlp->nlrows[i]->name, nlp->nlrows[i]->dualsol); */ 4760 assert(nlp->varmap_nlp2nlpi[i] >= 0); /* NLP was flushed before solve, so all vars should be in there */ 4765 /* SCIPdebugMessage("duals of var <%s> = %g %g\n", SCIPvarGetName(nlp->vars[i]), nlp->varlbdualvals[i], nlp->varubdualvals[i]); */ 4800 SCIPdebugMessage("calculating NLP fractional variables: validfracvars=%" SCIP_LONGINT_FORMAT ", nnlps=%" SCIP_LONGINT_FORMAT "\n", nlp->validfracvars, stat->nnlps); 4808 SCIPdebugMessage("NLP globally infeasible, unbounded, or worse -> no solution values -> no fractional variables\n"); 4848 if( SCIPvarGetType(var) != SCIP_VARTYPE_BINARY && SCIPvarGetType(var) != SCIP_VARTYPE_INTEGER ) 4851 /* ignore fixed variables (due to numerics, it is possible, that the NLP solution of a fixed integer variable 4869 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlp->fracvarssol, nlp->fracvarssize, newsize) ); 4870 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlp->fracvarsfrac, nlp->fracvarssize, newsize) ); 4900 * move away the first non-maximal priority candidate, move the current candidate to the correct 4925 SCIPdebugMessage(" -> %d fractional variables (%d of maximal priority)\n", nlp->nfracvars, nlp->npriofracvars); 4955 SCIP_CALL( SCIPnlpDelVar(scip->nlp, SCIPblkmem(scip), scip->set, scip->eventqueue, scip->lp, var) ); 4960 SCIPdebugMessage( "-> handling variable fixation event, variable <%s>\n", SCIPvarGetName(var) ); 4961 SCIP_CALL( nlpRemoveFixedVar(scip->nlp, SCIPblkmem(scip), scip->set, scip->stat, scip->eventqueue, scip->lp, var) ); 4965 SCIPdebugMessage( "-> handling bound changed event %x, variable <%s>\n", etype, SCIPvarGetName(var) ); 4966 SCIP_CALL( nlpUpdateVarBounds(scip->nlp, scip->set, var, SCIP_EVENTTYPE_BOUNDTIGHTENED & etype) ); 5019 int nvars_estimate /**< an estimate on the number of variables that may be added to the NLP later */ 5058 /* maybe someone wanna use the NLP just to collect nonlinearities, but is not necessarily interesting on solving 5076 SCIP_CALL( SCIPhashmapCreate(&(*nlp)->varhash, blkmem, SCIPcalcHashtableSize(5 * nvars_estimate)) ); 5260 SCIP_ALLOC( BMSreallocBlockMemoryArray(blkmem, &nlp->varmap_nlp2nlpi, nlp->sizevars, newsize) ); 5575 /** gets fractional variables of last NLP solution along with solution values and fractionalities 5583 SCIP_Real** fracvarssol, /**< pointer to store the array of NLP fractional variables solution values, or NULL */ 5584 SCIP_Real** fracvarsfrac, /**< pointer to store the array of NLP fractional variables fractionalities, or NULL */ 5586 int* npriofracvars /**< pointer to store the number of NLP fractional variables with maximal branching priority, or NULL */ 5668 /* if user wants to let NLP solver choose start point, then invalidate current initial guess both in NLP and in NLPI */ 5760 /** computes for each variables the number of NLP rows in which the variable appears in a nonlinear var */ 5763 int* nlcount /**< an array of length at least SCIPnlpGetNVars() to store nonlinearity counts of variables */ 5802 if( nlrow->quadvarshash != NULL && SCIPhashmapExists(nlrow->quadvarshash, (void*)exprtreevars[i]) ) /*lint !e613 */ 5805 varidx = (int)(size_t) SCIPhashmapGetImage(nlp->varhash, (void*)exprtreevars[i]); /*lint !e613 */ 5816 /** indicates whether there exists a row that contains a continuous variable in a nonlinear term 6094 /* In diving mode we do not cache changes but put them directly in the NLPI problem, which does not exist if there is no solver. 6143 SCIP_CALL( SCIPnlpiChgVarBounds(nlp->solver, nlp->problem, nlp->nvars, varidx, varlb, varub) ); SCIP_RETCODE SCIPnlpSetRealPar(SCIP_NLP *nlp, SCIP_NLPPARAM type, SCIP_Real dval) Definition: nlp.c:6025 static SCIP_RETCODE nlrowRemoveFixedLinearCoefs(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:1457 SCIP_RETCODE SCIPnlpiDelConsSet(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int *dstats) Definition: nlpi.c:377 static SCIP_RETCODE nlrowLinearCoefChanged(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_VAR *var, SCIP_Real coef, SCIP_NLP *nlp) Definition: nlp.c:491 static int nlrowSearchQuadElem(SCIP_NLROW *nlrow, int idx1, int idx2) Definition: nlp.c:1113 SCIP_RETCODE SCIPnlpEnsureNlRowsSize(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, int num) Definition: nlp.c:5363 SCIP_Real SCIPvarGetMultaggrConstant(SCIP_VAR *var) Definition: var.c:16861 static SCIP_RETCODE nlpEnsureVarsSolverSize(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, int num) Definition: nlp.c:4093 void SCIPquadelemSort(SCIP_QUADELEM *quadelems, int nquadelems) Definition: expr.c:9030 static SCIP_RETCODE nlrowExprtreeChanged(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:614 SCIP_RETCODE SCIPnlrowGetPseudoFeasibility(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_Real *pseudofeasibility) Definition: nlp.c:3043 SCIP_RETCODE SCIPsetIncludeEventhdlr(SCIP_SET *set, SCIP_EVENTHDLR *eventhdlr) Definition: set.c:3936 Definition: type_nlpi.h:65 #define BMSfreeBlockMemoryArrayNull(mem, ptr, num) Definition: memory.h:422 internal methods for managing events SCIP_RETCODE SCIPnlrowPrint(SCIP_NLROW *nlrow, SCIP_MESSAGEHDLR *messagehdlr, FILE *file) Definition: nlp.c:2279 SCIP_RETCODE SCIPnlrowChgRhs(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_Real rhs) Definition: nlp.c:2802 SCIP_RETCODE SCIPnlpiGetStringPar(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_NLPPARAM type, const char **sval) Definition: nlpi.c:684 internal methods for storing primal CIP solutions Definition: type_nlpi.h:64 SCIP_RETCODE SCIPexprtreeEvalInt(SCIP_EXPRTREE *tree, SCIP_Real infinity, SCIP_INTERVAL *varvals, SCIP_INTERVAL *val) Definition: expr.c:8579 Definition: intervalarith.h:36 SCIP_RETCODE SCIPvarSetNLPSol(SCIP_VAR *var, SCIP_SET *set, SCIP_Real solval) Definition: var.c:13260 SCIP_RETCODE SCIPeventhdlrCreate(SCIP_EVENTHDLR **eventhdlr, const char *name, const char *desc, SCIP_DECL_EVENTCOPY((*eventcopy)), SCIP_DECL_EVENTFREE((*eventfree)), SCIP_DECL_EVENTINIT((*eventinit)), SCIP_DECL_EVENTEXIT((*eventexit)), SCIP_DECL_EVENTINITSOL((*eventinitsol)), SCIP_DECL_EVENTEXITSOL((*eventexitsol)), SCIP_DECL_EVENTDELETE((*eventdelete)), SCIP_DECL_EVENTEXEC((*eventexec)), SCIP_EVENTHDLRDATA *eventhdlrdata) Definition: event.c:64 void SCIPexprtreePrint(SCIP_EXPRTREE *tree, SCIP_MESSAGEHDLR *messagehdlr, FILE *file, const char **varnames, const char **paramnames) Definition: expr.c:8596 static int nlrowSearchLinearCoef(SCIP_NLROW *nlrow, SCIP_VAR *var) Definition: nlp.c:840 static SCIP_RETCODE nlpUpdateVarBounds(SCIP_NLP *nlp, SCIP_SET *set, SCIP_VAR *var, SCIP_Bool tightened) Definition: nlp.c:3628 Definition: struct_scip.h:53 static SCIP_RETCODE nlrowAddQuadElement(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_QUADELEM elem) Definition: nlp.c:1157 Definition: type_nlpi.h:66 SCIP_RETCODE SCIPnlrowAddQuadElement(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_QUADELEM elem) Definition: nlp.c:2597 static SCIP_RETCODE nlpSetupNlpiIndices(SCIP_NLP *nlp, SCIP_SET *set, SCIP_NLROW *nlrow, int **linidxs, SCIP_QUADELEM **quadelems, int **nlinidxs) Definition: nlp.c:3978 static SCIP_RETCODE nlrowQuadElemChanged(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_QUADELEM quadelem, SCIP_NLP *nlp) Definition: nlp.c:541 SCIP_RETCODE SCIPnlrowRelease(SCIP_NLROW **nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:2346 internal methods for clocks and timing issues static SCIP_RETCODE nlrowChgQuadElemPos(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, int pos, SCIP_Real coef) Definition: nlp.c:1234 SCIP_EVENTHDLR * SCIPsetFindEventhdlr(SCIP_SET *set, const char *name) Definition: set.c:3959 static SCIP_RETCODE nlpFlushNlRowAdditions(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:4336 SCIP_RETCODE SCIPeventfilterDel(SCIP_EVENTFILTER *eventfilter, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTTYPE eventtype, SCIP_EVENTHDLR *eventhdlr, SCIP_EVENTDATA *eventdata, int filterpos) Definition: event.c:1808 internal methods for NLPI solver interfaces SCIP_RETCODE SCIPnlrowEnsureQuadVarsSize(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, int num) Definition: nlp.c:2514 SCIP_Real * SCIPexprtreeGetParamVals(SCIP_EXPRTREE *tree) Definition: expr.c:8472 Definition: struct_var.h:196 SCIP_RETCODE SCIPnlrowCreate(SCIP_NLROW **nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, const char *name, SCIP_Real constant, int nlinvars, SCIP_VAR **linvars, SCIP_Real *lincoefs, int nquadvars, SCIP_VAR **quadvars, int nquadelems, SCIP_QUADELEM *quadelems, SCIP_EXPRTREE *exprtree, SCIP_Real lhs, SCIP_Real rhs) Definition: nlp.c:1995 SCIP_RETCODE SCIPnlpGetStatistics(SCIP_NLP *nlp, SCIP_NLPSTATISTICS *statistics) Definition: nlp.c:5948 data definitions for expressions and expression trees Definition: type_nlpi.h:83 SCIP_RETCODE SCIPvarCatchEvent(SCIP_VAR *var, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTTYPE eventtype, SCIP_EVENTHDLR *eventhdlr, SCIP_EVENTDATA *eventdata, int *filterpos) Definition: var.c:17537 static SCIP_RETCODE nlpFlushVarDeletions(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:4242 SCIP_RETCODE SCIPnlpSolveDive(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_MESSAGEHDLR *messagehdlr, SCIP_STAT *stat) Definition: nlp.c:6308 SCIP_RETCODE SCIPhashmapCreate(SCIP_HASHMAP **hashmap, BMS_BLKMEM *blkmem, int mapsize) Definition: misc.c:2057 SCIP_RETCODE SCIPnlpGetVarsNonlinearity(SCIP_NLP *nlp, int *nlcount) Definition: nlp.c:5761 SCIP_RETCODE SCIPnlpiFreeProblem(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM **problem) Definition: nlpi.c:224 static SCIP_RETCODE nlrowRemoveFixedVar(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_VAR *var) Definition: nlp.c:1950 SCIP_RETCODE SCIPexprtreeSetVars(SCIP_EXPRTREE *tree, int nvars, SCIP_VAR **vars) Definition: nlp.c:111 Definition: struct_message.h:35 static SCIP_RETCODE nlpCalcFracVars(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat) Definition: nlp.c:4786 SCIP_RETCODE SCIPnlrowEnsureQuadElementsSize(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, int num) Definition: nlp.c:2573 SCIP_RETCODE SCIPnlpCreate(SCIP_NLP **nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, const char *name, int nvars_estimate) Definition: nlp.c:5013 Definition: type_var.h:53 SCIP_RETCODE SCIPnlpChgVarsBoundsDive(SCIP_NLP *nlp, SCIP_SET *set, int nvars, SCIP_VAR **vars, SCIP_Real *lbs, SCIP_Real *ubs) Definition: nlp.c:6256 SCIP_RETCODE SCIPexprtreeCopy(BMS_BLKMEM *blkmem, SCIP_EXPRTREE **targettree, SCIP_EXPRTREE *sourcetree) Definition: expr.c:8652 SCIP_RETCODE SCIPnlpiSetStringPar(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_NLPPARAM type, const char *sval) Definition: nlpi.c:701 datastructures for NLP management SCIP_RETCODE SCIPnlpGetPseudoObjval(SCIP_NLP *nlp, SCIP_SET *set, SCIP_STAT *stat, SCIP_Real *pseudoobjval) Definition: nlp.c:5548 void SCIPexprReindexVars(SCIP_EXPR *expr, int *newindices) Definition: expr.c:8029 void SCIPintervalSetBounds(SCIP_INTERVAL *resultant, SCIP_Real inf, SCIP_Real sup) Definition: intervalarith.c:479 Definition: type_expr.h:98 SCIP_RETCODE SCIPnlrowChgExprtreeParams(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_Real *paramvals) Definition: nlp.c:2740 SCIP_RETCODE SCIPnlpReset(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTQUEUE *eventqueue, SCIP_LP *lp) Definition: nlp.c:5193 Definition: type_expr.h:38 static SCIP_RETCODE nlrowConstantChanged(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:776 SCIP_RETCODE SCIPnlpiGetSolution(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_Real **primalvalues, SCIP_Real **consdualvalues, SCIP_Real **varlbdualvalues, SCIP_Real **varubdualvalues) Definition: nlpi.c:535 SCIP_RETCODE SCIPnlrowEnsureLinearSize(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, int num) Definition: nlp.c:2370 SCIP_RETCODE SCIPnlpiGetRealPar(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_NLPPARAM type, SCIP_Real *dval) Definition: nlpi.c:650 void * SCIPhashmapGetImage(SCIP_HASHMAP *hashmap, void *origin) Definition: misc.c:2116 SCIP_RETCODE SCIPnlpGetIntPar(SCIP_NLP *nlp, SCIP_NLPPARAM type, int *ival) Definition: nlp.c:5975 SCIP_Bool SCIPquadelemSortedFind(SCIP_QUADELEM *quadelems, int idx1, int idx2, int nquadelems, int *pos) Definition: expr.c:9055 void SCIPexprtreeSetParamVal(SCIP_EXPRTREE *tree, int paramidx, SCIP_Real paramval) Definition: expr.c:8482 SCIP_RETCODE SCIPnlrowChgQuadElem(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_QUADELEM elem) Definition: nlp.c:2646 SCIP_Bool SCIPsetIsFeasFracIntegral(SCIP_SET *set, SCIP_Real val) Definition: set.c:5732 SCIP_RETCODE SCIPnlrowChgLhs(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_Real lhs) Definition: nlp.c:2782 SCIP_RETCODE SCIPnlrowGetNLPFeasibility(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_Real *feasibility) Definition: nlp.c:2942 SCIP_RETCODE SCIPnlpDelNlRow(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_NLROW *nlrow) Definition: nlp.c:5443 Definition: type_nlpi.h:67 SCIP_Real SCIPsolGetVal(SCIP_SOL *sol, SCIP_SET *set, SCIP_STAT *stat, SCIP_VAR *var) Definition: sol.c:1245 public methods for expressions, expression trees, expression graphs, and related stuff ... SCIP_RETCODE SCIPnlpiChgConsSides(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int nconss, const int *indices, const SCIP_Real *lhss, const SCIP_Real *rhss) Definition: nlpi.c:343 Definition: struct_sol.h:50 Definition: struct_set.h:56 SCIP_Bool SCIPhashmapExists(SCIP_HASHMAP *hashmap, void *origin) Definition: misc.c:2159 static SCIP_RETCODE nlrowChgLinearCoefPos(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, int pos, SCIP_Real coef) Definition: nlp.c:1038 SCIP_RETCODE SCIPnlrowAddQuadVar(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_VAR *var) Definition: nlp.c:2538 static SCIP_RETCODE nlpSolve(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_MESSAGEHDLR *messagehdlr, SCIP_STAT *stat) Definition: nlp.c:4639 SCIP_RETCODE SCIPnlpStartDive(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:6078 static SCIP_RETCODE nlpFlushVarAdditions(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:4489 SCIP_Bool SCIPnlpHasContinuousNonlinearity(SCIP_NLP *nlp) Definition: nlp.c:5820 Definition: struct_misc.h:101 static SCIP_RETCODE nlrowRemoveFixedExprtreeVars(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:1917 static SCIP_RETCODE nlrowRemoveFixedQuadVars(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:1483 static SCIP_RETCODE nlpMoveVar(SCIP_NLP *nlp, int oldpos, int newpos) Definition: nlp.c:3827 SCIP_RETCODE SCIPnlpAddVars(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, int nvars, SCIP_VAR **vars) Definition: nlp.c:5302 void SCIPnlrowGetQuadData(SCIP_NLROW *nlrow, int *nquadvars, SCIP_VAR ***quadvars, int *nquadelems, SCIP_QUADELEM **quadelems) Definition: nlp.c:3332 static SCIP_RETCODE nlrowDelQuadElemPos(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, int pos) Definition: nlp.c:1202 #define BMSduplicateBlockMemoryArray(mem, ptr, source, num) Definition: memory.h:416 SCIP_NLPTERMSTAT SCIPnlpiGetTermstat(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem) Definition: nlpi.c:521 Definition: type_nlpi.h:63 SCIP_Bool SCIPintervalIsEntire(SCIP_Real infinity, SCIP_INTERVAL operand) Definition: intervalarith.c:528 SCIP_RETCODE SCIPeventfilterAdd(SCIP_EVENTFILTER *eventfilter, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTTYPE eventtype, SCIP_EVENTHDLR *eventhdlr, SCIP_EVENTDATA *eventdata, int *filterpos) Definition: event.c:1715 internal methods for storing and manipulating the main problem Definition: struct_nlpi.h:78 SCIP_RETCODE SCIPnlpiDelVarSet(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int *dstats) Definition: nlpi.c:361 interval arithmetics for provable bounds SCIP_RETCODE SCIPnlrowChgLinearCoef(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_VAR *var, SCIP_Real coef) Definition: nlp.c:2476 SCIP_Real SCIPintervalGetInf(SCIP_INTERVAL interval) Definition: intervalarith.c:451 SCIP_RETCODE SCIPnlpGetRealPar(SCIP_NLP *nlp, SCIP_NLPPARAM type, SCIP_Real *dval) Definition: nlp.c:6008 SCIP_RETCODE SCIPnlpiAddVars(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int nvars, const SCIP_Real *lbs, const SCIP_Real *ubs, const char **varnames) Definition: nlpi.c:250 SCIP_RETCODE SCIPvarRelease(SCIP_VAR **var, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTQUEUE *eventqueue, SCIP_LP *lp) Definition: var.c:2752 SCIP_RETCODE SCIPnlpiChgLinearCoefs(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, const int idx, int nvals, const int *varidxs, const SCIP_Real *vals) Definition: nlpi.c:393 SCIP_RETCODE SCIPnlrowGetPseudoActivity(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_Real *pseudoactivity) Definition: nlp.c:3017 SCIP_RETCODE SCIPnlrowDelLinearCoef(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_VAR *var) Definition: nlp.c:2443 SCIP_RETCODE SCIPnlpiSetIntPar(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_NLPPARAM type, int ival) Definition: nlpi.c:633 SCIP_Bool SCIPsortedvecFindPtr(void **ptrarray, SCIP_DECL_SORTPTRCOMP((*ptrcomp)), void *val, int len, int *pos) static SCIP_RETCODE nlpFlushObjective(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:4577 SCIP_RETCODE SCIPnlpiCreateProblem(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM **problem, const char *name) Definition: nlpi.c:211 SCIP_RETCODE SCIPnlrowGetSolFeasibility(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_SOL *sol, SCIP_Real *feasibility) Definition: nlp.c:3148 SCIP_RETCODE SCIPnlrowDelQuadElement(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, int idx1, int idx2) Definition: nlp.c:2612 internal methods for NLP management SCIP_RETCODE SCIPnlpSetIntPar(SCIP_NLP *nlp, SCIP_NLPPARAM type, int ival) Definition: nlp.c:5992 static SCIP_RETCODE nlpRowChanged(SCIP_NLP *nlp, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLROW *nlrow) Definition: nlp.c:3433 void SCIPmessagePrintWarning(SCIP_MESSAGEHDLR *messagehdlr, const char *formatstr,...) Definition: message.c:411 SCIP_Bool SCIPsetIsRelLE(SCIP_SET *set, SCIP_Real val1, SCIP_Real val2) Definition: set.c:6101 SCIP_RETCODE SCIPnlpiChgQuadCoefs(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int idx, int nquadelems, const SCIP_QUADELEM *quadelems) Definition: nlpi.c:411 SCIP_RETCODE SCIPnlpEnsureVarsSize(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, int num) Definition: nlp.c:5242 Definition: type_retcode.h:33 static SCIP_RETCODE nlpEnsureNlRowsSolverSize(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, int num) Definition: nlp.c:4121 internal methods for global SCIP settings SCIP main data structure. SCIP_Bool SCIPsetIsFeasGE(SCIP_SET *set, SCIP_Real val1, SCIP_Real val2) Definition: set.c:5666 static SCIP_RETCODE nlpDelNlRowPos(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, int pos) Definition: nlp.c:3575 static SCIP_RETCODE nlrowRemoveFixedLinearCoefPos(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, int pos) Definition: nlp.c:1357 SCIP_RETCODE SCIPnlpSetInitialGuess(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_Real *initguess) Definition: nlp.c:5657 void SCIPintervalSet(SCIP_INTERVAL *resultant, SCIP_Real value) Definition: intervalarith.c:467 SCIP_RETCODE SCIPnlrowCreateFromRow(SCIP_NLROW **nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_ROW *row) Definition: nlp.c:2177 SCIP_Bool SCIPsetIsEQ(SCIP_SET *set, SCIP_Real val1, SCIP_Real val2) Definition: set.c:5202 SCIP_RETCODE SCIPnlpChgVarObjDive(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_VAR *var, SCIP_Real coef) Definition: nlp.c:6169 SCIP_RETCODE SCIPvarPrint(SCIP_VAR *var, SCIP_SET *set, SCIP_MESSAGEHDLR *messagehdlr, FILE *file) Definition: var.c:2873 SCIP_RETCODE SCIPnlrowChgConstant(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_Real constant) Definition: nlp.c:2762 SCIP_RETCODE SCIPnlpChgVarBoundsDive(SCIP_NLP *nlp, SCIP_VAR *var, SCIP_Real lb, SCIP_Real ub) Definition: nlp.c:6228 SCIP_Bool SCIPsetIsFeasLE(SCIP_SET *set, SCIP_Real val1, SCIP_Real val2) Definition: set.c:5622 SCIP_RETCODE SCIPnlrowChgExprtreeParam(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, int paramidx, SCIP_Real paramval) Definition: nlp.c:2717 static SCIP_RETCODE nlpAddVars(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, int nvars, SCIP_VAR **vars) Definition: nlp.c:3748 Definition: type_retcode.h:34 SCIP_RETCODE SCIPexprtreeRemoveFixedVars(SCIP_EXPRTREE *tree, SCIP_SET *set, SCIP_Bool *changed, int *varpos, int *newvarsstart) Definition: nlp.c:223 static SCIP_RETCODE nlrowSideChanged(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:738 Definition: struct_expr.h:46 internal methods for problem variables SCIP_RETCODE SCIPnlpWrite(SCIP_NLP *nlp, SCIP_SET *set, SCIP_MESSAGEHDLR *messagehdlr, const char *fname) Definition: nlp.c:5690 public data structures and miscellaneous methods SCIP_RETCODE SCIPnlpEndDive(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:6108 SCIP_RETCODE SCIPnlpiSetRealPar(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_NLPPARAM type, SCIP_Real dval) Definition: nlpi.c:668 Definition: type_expr.h:37 static SCIP_RETCODE nlrowAddLinearCoef(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_VAR *var, SCIP_Real coef) Definition: nlp.c:885 SCIP_RETCODE SCIPnlpiSetObjective(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int nlins, const int *lininds, const SCIP_Real *linvals, int nquadelems, const SCIP_QUADELEM *quadelems, const int *exprvaridxs, const SCIP_EXPRTREE *exprtree, const SCIP_Real constant) Definition: nlpi.c:300 SCIP_RETCODE SCIPnlpiSetInitialGuess(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_Real *primalvalues, SCIP_Real *consdualvalues, SCIP_Real *varlbdualvalues, SCIP_Real *varubdualvalues) Definition: nlpi.c:477 SCIP_RETCODE SCIPnlpAddNlRow(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLROW *nlrow) Definition: nlp.c:5391 static SCIP_RETCODE nlpDelVarPos(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTQUEUE *eventqueue, SCIP_LP *lp, int pos) Definition: nlp.c:3860 Definition: type_var.h:54 SCIP_RETCODE SCIPnlpFlush(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:5474 Definition: struct_lp.h:189 SCIP_RETCODE SCIPnlpiGetIntPar(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_NLPPARAM type, int *ival) Definition: nlpi.c:616 public methods for LP management SCIP_RETCODE SCIPnlpiChgVarBounds(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int nvars, const int *indices, const SCIP_Real *lbs, const SCIP_Real *ubs) Definition: nlpi.c:325 SCIP_RETCODE SCIPexprCreate(BMS_BLKMEM *blkmem, SCIP_EXPR **expr, SCIP_EXPROP op,...) Definition: expr.c:5853 SCIP_RETCODE SCIPnlrowGetNLPActivity(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_Real *activity) Definition: nlp.c:2915 Definition: type_var.h:45 void SCIPintervalAdd(SCIP_Real infinity, SCIP_INTERVAL *resultant, SCIP_INTERVAL operand1, SCIP_INTERVAL operand2) Definition: intervalarith.c:677 SCIP_RETCODE SCIPnlrowChgExprtree(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_EXPRTREE *exprtree) Definition: nlp.c:2678 SCIP_Real SCIPintervalGetSup(SCIP_INTERVAL interval) Definition: intervalarith.c:459 SCIP_RETCODE SCIPnlrowRemoveFixedVars(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:2822 SCIP_RETCODE SCIPnlpiSolve(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem) Definition: nlpi.c:495 SCIP_Real * SCIPvarGetMultaggrScalars(SCIP_VAR *var) Definition: var.c:16849 SCIP_RETCODE SCIPnlrowGetActivityBounds(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_Real *minactivity, SCIP_Real *maxactivity) Definition: nlp.c:3169 SCIP_RETCODE SCIPnlpGetFracVars(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_VAR ***fracvars, SCIP_Real **fracvarssol, SCIP_Real **fracvarsfrac, int *nfracvars, int *npriofracvars) Definition: nlp.c:5577 SCIP_Bool SCIPsetIsFeasLT(SCIP_SET *set, SCIP_Real val1, SCIP_Real val2) Definition: set.c:5600 SCIP_RETCODE SCIPnlrowGetSolActivity(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_SOL *sol, SCIP_Real *activity) Definition: nlp.c:3063 Definition: type_retcode.h:39 SCIP_RETCODE SCIPnlpSolve(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_MESSAGEHDLR *messagehdlr, SCIP_STAT *stat) Definition: nlp.c:5511 static SCIP_RETCODE nlpFlushNlRowDeletions(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set) Definition: nlp.c:4149 SCIP_RETCODE SCIPnlpDelVar(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTQUEUE *eventqueue, SCIP_LP *lp, SCIP_VAR *var) Definition: nlp.c:5327 Definition: type_set.h:33 SCIP_RETCODE SCIPhashmapRemove(SCIP_HASHMAP *hashmap, void *origin) Definition: misc.c:2177 SCIP_RETCODE SCIPnlrowAddLinearCoef(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_VAR *var, SCIP_Real val) Definition: nlp.c:2395 static SCIP_RETCODE nlrowDelLinearCoefPos(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, int pos) Definition: nlp.c:1009 Definition: type_nlpi.h:61 static SCIP_RETCODE nlrowSetupQuadVarsHash(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem) Definition: nlp.c:1068 SCIP_RETCODE SCIPnlrowFree(SCIP_NLROW **nlrow, BMS_BLKMEM *blkmem) Definition: nlp.c:2242 Definition: struct_lp.h:255 SCIP_RETCODE SCIPnlpFree(SCIP_NLP **nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTQUEUE *eventqueue, SCIP_LP *lp) Definition: nlp.c:5134 SCIP_RETCODE SCIPnlpiChgExprtree(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int idxcons, const int *exprvaridxs, SCIP_EXPRTREE *exprtree) Definition: nlpi.c:428 static void nlrowMoveQuadElement(SCIP_NLROW *nlrow, int oldpos, int newpos) Definition: nlp.c:1136 SCIP_RETCODE SCIPnlrowRecalcNLPActivity(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp) Definition: nlp.c:2838 public methods for message output Definition: struct_nlp.h:107 static SCIP_RETCODE nlpUpdateObjCoef(SCIP_NLP *nlp, SCIP_VAR *var) Definition: nlp.c:3687 void SCIPmessageFPrintInfo(SCIP_MESSAGEHDLR *messagehdlr, FILE *file, const char *formatstr,...) Definition: message.c:602 SCIP_RETCODE SCIPhashmapSetImage(SCIP_HASHMAP *hashmap, void *origin, void *image) Definition: misc.c:2137 internal methods for problem statistics static SCIP_RETCODE nlpRemoveFixedVar(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_EVENTQUEUE *eventqueue, SCIP_LP *lp, SCIP_VAR *var) Definition: nlp.c:3946 static SCIP_RETCODE nlrowExprtreeParamChanged(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, int paramidx, SCIP_NLP *nlp) Definition: nlp.c:681 void SCIPintervalMulScalar(SCIP_Real infinity, SCIP_INTERVAL *resultant, SCIP_INTERVAL operand1, SCIP_Real operand2) Definition: intervalarith.c:1102 static SCIP_RETCODE nlrowCalcActivityBounds(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat) Definition: nlp.c:1265 Definition: struct_nlp.h:62 SCIP_RETCODE SCIPnlpiAddConstraints(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int nconss, const SCIP_Real *lhss, const SCIP_Real *rhss, const int *nlininds, int *const *lininds, SCIP_Real *const *linvals, const int *nquadelems, SCIP_QUADELEM *const *quadelems, int *const *exprvaridxs, SCIP_EXPRTREE *const *exprtrees, const char **names) Definition: nlpi.c:268 SCIP_RETCODE SCIPnlpAddNlRows(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, int nnlrows, SCIP_NLROW **nlrows) Definition: nlp.c:5415 void SCIPsortPtrReal(void **ptrarray, SCIP_Real *realarray, SCIP_DECL_SORTPTRCOMP((*ptrcomp)), int len) SCIP_RETCODE SCIPexprtreeSubstituteVars(SCIP_EXPRTREE *tree, SCIP_EXPR **substexprs) Definition: expr.c:8866 SCIP_RETCODE SCIPnlpSetStringPar(SCIP_NLP *nlp, SCIP_NLPPARAM type, const char *sval) Definition: nlp.c:6058 SCIP_RETCODE SCIPexprtreePrintWithNames(SCIP_EXPRTREE *tree, SCIP_MESSAGEHDLR *messagehdlr, FILE *file) Definition: nlp.c:172 Definition: type_retcode.h:45 SCIP_Bool SCIPsetIsFeasGT(SCIP_SET *set, SCIP_Real val1, SCIP_Real val2) Definition: set.c:5644 Definition: type_nlpi.h:62 SCIP_RETCODE SCIPnlpGetStringPar(SCIP_NLP *nlp, SCIP_NLPPARAM type, const char **sval) Definition: nlp.c:6041 static SCIP_RETCODE nlrowAddToLinearCoef(SCIP_NLROW *nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, SCIP_NLP *nlp, SCIP_VAR *var, SCIP_Real coef, SCIP_Bool removefixed) Definition: nlp.c:932 static SCIP_RETCODE nlpAddNlRows(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat, int nnlrows, SCIP_NLROW **nlrows) Definition: nlp.c:3468 Definition: struct_stat.h:44 Definition: struct_expr.h:55 SCIP_RETCODE SCIPvarDropEvent(SCIP_VAR *var, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_EVENTTYPE eventtype, SCIP_EVENTHDLR *eventhdlr, SCIP_EVENTDATA *eventdata, int filterpos) Definition: var.c:17564 SCIP_RETCODE SCIPhashmapInsert(SCIP_HASHMAP *hashmap, void *origin, void *image) Definition: misc.c:2094 common defines and data types used in all packages of SCIP SCIP_RETCODE SCIPnlpiChgNonlinCoef(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, int considx, int paramidx, SCIP_Real value) Definition: nlpi.c:445 Definition: struct_event.h:204 SCIP_RETCODE SCIPvarGetProbvarSum(SCIP_VAR **var, SCIP_SET *set, SCIP_Real *scalar, SCIP_Real *constant) Definition: var.c:11906 SCIP_RETCODE SCIPnlpRemoveRedundantNlRows(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_STAT *stat) Definition: nlp.c:5611 Definition: type_retcode.h:43 SCIP_RETCODE SCIPexprCreateLinear(BMS_BLKMEM *blkmem, SCIP_EXPR **expr, int nchildren, SCIP_EXPR **children, SCIP_Real *coefs, SCIP_Real constant) Definition: expr.c:6380 Definition: objbranchrule.h:33 SCIP_RETCODE SCIPnlpiGetStatistics(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem, SCIP_NLPSTATISTICS *statistics) Definition: nlpi.c:553 int SCIPnlrowSearchQuadVar(SCIP_NLROW *nlrow, SCIP_VAR *var) Definition: nlp.c:3285 SCIP_RETCODE SCIPnlrowRecalcPseudoActivity(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat) Definition: nlp.c:2962 SCIP_RETCODE SCIPexprtreeSetParams(SCIP_EXPRTREE *tree, int nparams, SCIP_Real *paramvals) Definition: expr.c:8716 static void nlrowMoveLinearCoef(SCIP_NLROW *nlrow, int oldpos, int newpos) Definition: nlp.c:862 SCIP_RETCODE SCIPnlrowIsRedundant(SCIP_NLROW *nlrow, SCIP_SET *set, SCIP_STAT *stat, SCIP_Bool *isredundant) Definition: nlp.c:3200 SCIP_RETCODE SCIPnlpAddVar(SCIP_NLP *nlp, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_VAR *var) Definition: nlp.c:5276 datastructures for global SCIP settings Definition: nlpi_ipopt.cpp:124 #define BMSreallocBlockMemoryArray(mem, ptr, oldnum, newnum) Definition: memory.h:412 SCIP_RETCODE SCIPexprtreeAddVars(SCIP_EXPRTREE *tree, int nvars, SCIP_VAR **vars) Definition: nlp.c:143 SCIP_RETCODE SCIPnlrowCreateCopy(SCIP_NLROW **nlrow, BMS_BLKMEM *blkmem, SCIP_SET *set, SCIP_NLROW *sourcenlrow) Definition: nlp.c:2142 Definition: struct_event.h:185 SCIP_NLPSOLSTAT SCIPnlpiGetSolstat(SCIP_NLPI *nlpi, SCIP_NLPIPROBLEM *problem) Definition: nlpi.c:509 SCIP_Bool SCIPsetIsFeasNegative(SCIP_SET *set, SCIP_Real val) Definition: set.c:5710 SCIP_RETCODE SCIPexprtreeEval(SCIP_EXPRTREE *tree, SCIP_Real *varvals, SCIP_Real *val) Definition: expr.c:8563 void SCIPintervalQuad(SCIP_Real infinity, SCIP_INTERVAL *resultant, SCIP_Real sqrcoeff, SCIP_INTERVAL lincoeff, SCIP_INTERVAL xrng) Definition: intervalarith.c:2775 Definition: struct_nlpi.h:35 Definition: type_var.h:56 |