Scippy

SCIP

Solving Constraint Integer Programs

sepa_aggregation.c
Go to the documentation of this file.
1 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
2 /* */
3 /* This file is part of the program and library */
4 /* SCIP --- Solving Constraint Integer Programs */
5 /* */
6 /* Copyright (C) 2002-2019 Konrad-Zuse-Zentrum */
7 /* fuer Informationstechnik Berlin */
8 /* */
9 /* SCIP is distributed under the terms of the ZIB Academic License. */
10 /* */
11 /* You should have received a copy of the ZIB Academic License */
12 /* along with SCIP; see the file COPYING. If not visit scip.zib.de. */
13 /* */
14 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
15 
16 /**@file sepa_aggregation.c
17  * @brief flow cover and complemented mixed integer rounding cuts separator (Marchand's version)
18  * @author Robert Lion Gottwald
19  * @author Kati Wolter
20  * @author Tobias Achterberg
21  *
22  * For an overview see:
23  *
24  * Marchand, H., & Wolsey, L. A. (2001).@n
25  * Aggregation and mixed integer rounding to solve MIPs.@n
26  * Operations research, 49(3), 363-371.
27  *
28  * Some remarks:
29  * - In general, continuous variables are less prefered than integer variables, since their cut
30  * coefficient is worse.
31  * - We seek for aggregations that project out continuous variables that are far away from their bound,
32  * since if it is at its bound then it doesn't contribute to the violation
33  * - These aggregations are also useful for the flowcover separation, so after building an aggregation
34  * we try to generate a MIR cut and a flowcover cut.
35  * - We only keep the best cut.
36  */
37 
38 /*---+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8----+----9----+----0----+----1----+----2*/
39 
40 #include "blockmemshell/memory.h"
41 #include "scip/cuts.h"
42 #include "scip/pub_lp.h"
43 #include "scip/pub_message.h"
44 #include "scip/pub_misc.h"
45 #include "scip/pub_misc_sort.h"
46 #include "scip/pub_sepa.h"
47 #include "scip/pub_var.h"
48 #include "scip/scip_branch.h"
49 #include "scip/scip_cut.h"
50 #include "scip/scip_general.h"
51 #include "scip/scip_lp.h"
52 #include "scip/scip_mem.h"
53 #include "scip/scip_message.h"
54 #include "scip/scip_numerics.h"
55 #include "scip/scip_param.h"
56 #include "scip/scip_prob.h"
57 #include "scip/scip_sepa.h"
58 #include "scip/scip_sol.h"
59 #include "scip/scip_solvingstats.h"
60 #include "scip/scip_tree.h"
61 #include "scip/scip_var.h"
62 #include "scip/sepa_aggregation.h"
63 #include <string.h>
64 
65 
66 #define SEPA_NAME "aggregation"
67 #define SEPA_DESC "aggregation heuristic for complemented mixed integer rounding cuts and flowcover cuts"
68 #define SEPA_PRIORITY -3000
69 #define SEPA_FREQ 10
70 #define SEPA_MAXBOUNDDIST 1.0
71 #define SEPA_USESSUBSCIP FALSE /**< does the separator use a secondary SCIP instance? */
72 #define SEPA_DELAY FALSE /**< should separation method be delayed, if other separators found cuts? */
73 
74 #define DEFAULT_MAXROUNDS -1 /**< maximal number of cmir separation rounds per node (-1: unlimited) */
75 #define DEFAULT_MAXROUNDSROOT -1 /**< maximal number of cmir separation rounds in the root node (-1: unlimited) */
76 #define DEFAULT_MAXTRIES 200 /**< maximal number of rows to start aggregation with per separation round
77  * (-1: unlimited) */
78 #define DEFAULT_MAXTRIESROOT -1 /**< maximal number of rows to start aggregation with per round in the root node
79  * (-1: unlimited) */
80 #define DEFAULT_MAXFAILS 20 /**< maximal number of consecutive unsuccessful aggregation tries (-1: unlimited) */
81 #define DEFAULT_MAXFAILSROOT 100 /**< maximal number of consecutive unsuccessful aggregation tries in the root node
82  * (-1: unlimited) */
83 #define DEFAULT_MAXAGGRS 3 /**< maximal number of aggregations for each row per separation round */
84 #define DEFAULT_MAXAGGRSROOT 6 /**< maximal number of aggregations for each row per round in the root node */
85 #define DEFAULT_MAXSEPACUTS 100 /**< maximal number of cmir cuts separated per separation round */
86 #define DEFAULT_MAXSEPACUTSROOT 500 /**< maximal number of cmir cuts separated per separation round in root node */
87 #define DEFAULT_MAXSLACK 0.0 /**< maximal slack of rows to be used in aggregation */
88 #define DEFAULT_MAXSLACKROOT 0.1 /**< maximal slack of rows to be used in aggregation in the root node */
89 #define DEFAULT_DENSITYSCORE 1e-4 /**< weight of row density in the aggregation scoring of the rows */
90 #define DEFAULT_SLACKSCORE 1e-3 /**< weight of slack in the aggregation scoring of the rows */
91 #define DEFAULT_MAXAGGDENSITY 0.20 /**< maximal density of aggregated row */
92 #define DEFAULT_MAXROWDENSITY 0.05 /**< maximal density of row to be used in aggregation */
93 #define DEFAULT_DENSITYOFFSET 100 /**< additional number of variables allowed in row on top of density */
94 #define DEFAULT_MAXROWFAC 1e+4 /**< maximal row aggregation factor */
95 #define DEFAULT_MAXTESTDELTA -1 /**< maximal number of different deltas to try (-1: unlimited) */
96 #define DEFAULT_AGGRTOL 1e-2 /**< aggregation heuristic: we try to delete continuous variables from the current
97  * aggregation, whose distance to its tightest bound is >= L - DEFAULT_AGGRTOL,
98  * where L is the largest of the distances between a continuous variable's value
99  * and its tightest bound in the current aggregation */
100 #define DEFAULT_TRYNEGSCALING TRUE /**< should negative values also be tested in scaling? */
101 #define DEFAULT_FIXINTEGRALRHS TRUE /**< should an additional variable be complemented if f0 = 0? */
102 #define DEFAULT_DYNAMICCUTS TRUE /**< should generated cuts be removed from the LP if they are no longer tight? */
103 
104 #define BOUNDSWITCH 0.5
105 #define POSTPROCESS TRUE
106 #define USEVBDS TRUE
107 #define MINFRAC 0.05
108 #define MAXFRAC 0.999
109 #define MAKECONTINTEGRAL FALSE
110 #define IMPLINTSARECONT
113 /*
114  * Data structures
115  */
117 /** separator data */
118 struct SCIP_SepaData
119 {
120  SCIP_Real maxslack; /**< maximal slack of rows to be used in aggregation */
121  SCIP_Real maxslackroot; /**< maximal slack of rows to be used in aggregation in the root node */
122  SCIP_Real densityscore; /**< weight of row density in the aggregation scoring of the rows */
123  SCIP_Real slackscore; /**< weight of slack in the aggregation scoring of the rows */
124  SCIP_Real maxaggdensity; /**< maximal density of aggregated row */
125  SCIP_Real maxrowdensity; /**< maximal density of row to be used in aggregation */
126  SCIP_Real maxrowfac; /**< maximal row aggregation factor */
127  SCIP_Real aggrtol; /**< tolerance for bound distance used in aggregation heuristic */
128  int maxrounds; /**< maximal number of cmir separation rounds per node (-1: unlimited) */
129  int maxroundsroot; /**< maximal number of cmir separation rounds in the root node (-1: unlimited) */
130  int maxtries; /**< maximal number of rows to start aggregation with per separation round
131  * (-1: unlimited) */
132  int maxtriesroot; /**< maximal number of rows to start aggregation with per round in the root node
133  * (-1: unlimited) */
134  int maxfails; /**< maximal number of consecutive unsuccessful aggregation tries
135  * (-1: unlimited) */
136  int maxfailsroot; /**< maximal number of consecutive unsuccessful aggregation tries in the root
137  * node (-1: unlimited) */
138  int maxaggrs; /**< maximal number of aggregations for each row per separation round */
139  int maxaggrsroot; /**< maximal number of aggregations for each row per round in the root node */
140  int maxsepacuts; /**< maximal number of cmir cuts separated per separation round */
141  int maxsepacutsroot; /**< maximal number of cmir cuts separated per separation round in root node */
142  int densityoffset; /**< additional number of variables allowed in row on top of density */
143  int maxtestdelta; /**< maximal number of different deltas to try (-1: unlimited) */
144  SCIP_Bool trynegscaling; /**< should negative values also be tested in scaling? */
145  SCIP_Bool fixintegralrhs; /**< should an additional variable be complemented if f0 = 0? */
146  SCIP_Bool dynamiccuts; /**< should generated cuts be removed from the LP if they are no longer tight? */
147  SCIP_Bool sepflowcover; /**< whether flowcover cuts should be separated in the current call */
148  SCIP_Bool sepcmir; /**< whether cMIR cuts should be separated in the current call */
149  SCIP_SEPA* cmir; /**< separator for adding cmir cuts */
150  SCIP_SEPA* flowcover; /**< separator for adding flowcover cuts */
151 };
152 
153 /** data used for aggregation of row */
154 typedef
155 struct AggregationData {
156  SCIP_Real* bounddist; /**< bound distance of continuous variables */
157  int* bounddistinds; /**< problem indices of the continUous variables corresponding to the bounddistance value */
158  int nbounddistvars; /**< number of continuous variables that are not at their bounds */
159  SCIP_ROW** aggrrows; /**< array of rows suitable for substitution of continuous variable */
160  SCIP_Real* aggrrowscoef; /**< coefficient of continuous variable in row that is suitable for substitution of that variable */
161  int aggrrowssize; /**< size of aggrrows array */
162  int naggrrows; /**< occupied positions in aggrrows array */
163  int* aggrrowsstart; /**< array with start positions of suitable rows for substitution for each
164  * continuous variable with non-zero bound distance */
165  int* ngoodaggrrows; /**< array with number of rows suitable for substitution that only contain
166  * one continuous variable that is not at it's bound */
167  int* nbadvarsinrow; /**< number of continuous variables that are not at their bounds for each row */
168  SCIP_AGGRROW* aggrrow; /**< store aggregation row here so that it can be reused */
170 
171 /*
172  * Local methods
173  */
175 /** adds given cut to LP if violated */
176 static
178  SCIP* scip, /**< SCIP data structure */
179  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
180  SCIP_SEPA* sepa, /**< separator */
181  SCIP_Bool makeintegral, /**< should cut be scaled to integral coefficients if possible? */
182  SCIP_Real* cutcoefs, /**< coefficients of active variables in cut */
183  int* cutinds, /**< problem indices of variables in cut */
184  int cutnnz, /**< number of non-zeros in cut */
185  SCIP_Real cutrhs, /**< right hand side of cut */
186  SCIP_Real cutefficacy, /**< efficacy of cut */
187  SCIP_Bool cutislocal, /**< is the cut only locally valid? */
188  SCIP_Bool cutremovable, /**< should the cut be removed from the LP due to aging or cleanup? */
189  int cutrank, /**< rank of the cut */
190  const char* cutclassname, /**< name of cut class to use for row names */
191  SCIP_Bool* cutoff, /**< whether a cutoff has been detected */
192  int* ncuts, /**< pointer to count the number of added cuts */
193  SCIP_ROW** thecut /**< pointer to return cut if it was added */
194  )
195 {
196  assert(scip != NULL);
197  assert(cutcoefs != NULL);
198  assert(cutoff != NULL);
199  assert(ncuts != NULL);
200 
201  *cutoff = FALSE;
202 
203  if( cutnnz > 0 && SCIPisEfficacious(scip, cutefficacy) )
204  {
205  SCIP_VAR** vars;
206  int i;
207  SCIP_ROW* cut;
208  char cutname[SCIP_MAXSTRLEN];
209  SCIP_Bool success;
210 
211  /* get active problem variables */
212  vars = SCIPgetVars(scip);
213 
214  /* create cut name */
215  (void) SCIPsnprintf(cutname, SCIP_MAXSTRLEN, "%s%d_%d", cutclassname, SCIPgetNLPs(scip), *ncuts);
216 
217 tryagain:
218  SCIP_CALL( SCIPcreateEmptyRowSepa(scip, &cut, sepa, cutname, -SCIPinfinity(scip), cutrhs, cutislocal, FALSE, cutremovable) );
219 
220  SCIP_CALL( SCIPcacheRowExtensions(scip, cut) );
221 
222  for( i = 0; i < cutnnz; ++i )
223  {
224  SCIP_CALL( SCIPaddVarToRow(scip, cut, vars[cutinds[i]], cutcoefs[i]) );
225  }
226 
227  /* set cut rank */
228  SCIProwChgRank(cut, cutrank);
229 
230  SCIPdebugMsg(scip, " -> found potential %s cut <%s>: rhs=%f, eff=%f\n", cutclassname, cutname, cutrhs, cutefficacy);
231  SCIPdebug( SCIP_CALL( SCIPprintRow(scip, cut, NULL) ) );
232 
233  /* if requested, try to scale the cut to integral values but only if the scaling is small; otherwise keep the fractional cut */
234  if( makeintegral && SCIPgetRowNumIntCols(scip, cut) == SCIProwGetNNonz(cut) )
235  {
236  SCIP_CALL( SCIPmakeRowIntegral(scip, cut, -SCIPepsilon(scip), SCIPsumepsilon(scip),
237  1000LL, 1000.0, MAKECONTINTEGRAL, &success) );
238 
239  if( SCIPisInfinity(scip, SCIProwGetRhs(cut)) )
240  {
241  /* release the row */
242  SCIP_CALL( SCIPreleaseRow(scip, &cut) );
243 
244  /* the scaling destroyed the cut, so try to add it again, but this time do not scale it */
245  makeintegral = FALSE;
246  goto tryagain;
247  }
248  }
249  else
250  {
251  success = FALSE;
252  }
253 
254  if( success && !SCIPisCutEfficacious(scip, sol, cut) )
255  {
256  SCIPdebugMsg(scip, " -> %s cut <%s> no longer efficacious: rhs=%f, eff=%f\n", cutclassname, cutname, cutrhs, cutefficacy);
257  SCIPdebug( SCIP_CALL( SCIPprintRow(scip, cut, NULL) ) );
258 
259  SCIP_CALL( SCIPreleaseRow(scip, &cut) );
260 
261  /* the cut is not efficacious anymore due to the scaling, so do not add it */
262  return SCIP_OKAY;
263  }
264 
265  SCIPdebugMsg(scip, " -> found %s cut <%s>: rhs=%f, eff=%f, rank=%d, min=%f, max=%f (range=%g)\n",
266  cutclassname, cutname, cutrhs, cutefficacy, SCIProwGetRank(cut),
267  SCIPgetRowMinCoef(scip, cut), SCIPgetRowMaxCoef(scip, cut),
268  SCIPgetRowMaxCoef(scip, cut)/SCIPgetRowMinCoef(scip, cut));
269  SCIPdebug( SCIP_CALL( SCIPprintRow(scip, cut, NULL) ) );
270 
271  SCIP_CALL( SCIPflushRowExtensions(scip, cut) );
272 
273  if( SCIPisCutNew(scip, cut) )
274  {
275  (*ncuts)++;
276 
277  if( !cutislocal )
278  {
279  SCIP_CALL( SCIPaddPoolCut(scip, cut) );
280  }
281  else
282  {
283  SCIP_CALL( SCIPaddRow(scip, cut, FALSE, cutoff) );
284  }
285 
286  *thecut = cut;
287  }
288  else
289  {
290  /* release the row */
291  SCIP_CALL( SCIPreleaseRow(scip, &cut) );
292  }
293  }
294 
295  return SCIP_OKAY;
296 }
297 
298 /** setup data for aggregating rows */
299 static
301  SCIP* scip, /**< SCIP data structure */
302  SCIP_SOL* sol, /**< solution to separate, NULL for LP solution */
303  SCIP_Bool allowlocal, /**< should local cuts be allowed */
304  AGGREGATIONDATA* aggrdata /**< pointer to aggregation data to setup */
305  )
306 {
307  SCIP_VAR** vars;
308  int nvars;
309  int nbinvars;
310  int nintvars;
311  int ncontvars;
312  int firstcontvar;
313  int nimplvars;
314  SCIP_ROW** rows;
315  int nrows;
316  int i;
317 
318  SCIP_CALL( SCIPgetVarsData(scip, &vars, &nvars, &nbinvars, &nintvars, &nimplvars, &ncontvars) );
319  SCIP_CALL( SCIPgetLPRowsData(scip, &rows, &nrows) );
320 
321  SCIP_CALL( SCIPallocBufferArray(scip, &aggrdata->bounddist, ncontvars + nimplvars) );
322  SCIP_CALL( SCIPallocBufferArray(scip, &aggrdata->bounddistinds, ncontvars + nimplvars) );
323  SCIP_CALL( SCIPallocBufferArray(scip, &aggrdata->ngoodaggrrows, ncontvars + nimplvars) );
324  SCIP_CALL( SCIPallocBufferArray(scip, &aggrdata->aggrrowsstart, ncontvars + nimplvars + 1) );
325  SCIP_CALL( SCIPallocBufferArray(scip, &aggrdata->nbadvarsinrow, nrows) );
326  SCIP_CALL( SCIPaggrRowCreate(scip, &aggrdata->aggrrow) );
327  BMSclearMemoryArray(aggrdata->nbadvarsinrow, nrows);
328 
329  aggrdata->nbounddistvars = 0;
330  aggrdata->aggrrows = NULL;
331  aggrdata->aggrrowscoef = NULL;
332  aggrdata->aggrrowssize = 0;
333  aggrdata->naggrrows = 0;
334 
335  firstcontvar = nvars - ncontvars;
336 
337  for( i = nbinvars + nintvars; i < nvars; ++i )
338  {
339  SCIP_Real bounddist;
340  SCIP_Real primsol;
341  SCIP_Real distlb;
342  SCIP_Real distub;
343  SCIP_Real bestlb;
344  SCIP_Real bestub;
345  SCIP_Real bestvlb;
346  SCIP_Real bestvub;
347  int bestvlbidx;
348  int bestvubidx;
349 
350  /* compute the bound distance of the variable */
351  if( allowlocal )
352  {
353  bestlb = SCIPvarGetLbLocal(vars[i]);
354  bestub = SCIPvarGetUbLocal(vars[i]);
355  }
356  else
357  {
358  bestlb = SCIPvarGetLbGlobal(vars[i]);
359  bestub = SCIPvarGetUbGlobal(vars[i]);
360  }
361 
362  SCIP_CALL( SCIPgetVarClosestVlb(scip, vars[i], sol, &bestvlb, &bestvlbidx) );
363  SCIP_CALL( SCIPgetVarClosestVub(scip, vars[i], sol, &bestvub, &bestvubidx) );
364  if( bestvlbidx >= 0 )
365  bestlb = MAX(bestlb, bestvlb);
366  if( bestvubidx >= 0 )
367  bestub = MIN(bestub, bestvub);
368 
369  primsol = SCIPgetSolVal(scip, sol, vars[i]);
370  distlb = primsol - bestlb;
371  distub = bestub - primsol;
372 
373  bounddist = MIN(distlb, distub);
374  bounddist = MAX(bounddist, 0.0);
375 
376  /* prefer continuous variables over implicit integers to be aggregated out */
377  if( i < firstcontvar )
378  bounddist *= 0.1;
379 
380  /* when variable is not at its bound, we want to project it out, so add it to the aggregation data */
381  if( !SCIPisZero(scip, bounddist) )
382  {
383  int k = aggrdata->nbounddistvars++;
384 
385  aggrdata->bounddist[k] = bounddist;
386  aggrdata->bounddistinds[k] = i;
387  aggrdata->aggrrowsstart[k] = aggrdata->naggrrows;
388 
389  /* the current variable is a bad variable (continuous, not at its bound): increase the number of bad variable
390  * count on each row this variables appears in; also each of these rows can be used to project the variable out
391  * so store them.
392  */
393  if( SCIPvarIsInLP(vars[i]) )
394  {
395  SCIP_COL* col = SCIPvarGetCol(vars[i]);
396  SCIP_ROW** colrows = SCIPcolGetRows(col);
397  SCIP_Real* colrowvals = SCIPcolGetVals(col);
398  int ncolnonzeros = SCIPcolGetNLPNonz(col);
399  int aggrrowsminsize = aggrdata->naggrrows + ncolnonzeros;
400 
401  if( aggrrowsminsize > aggrdata->aggrrowssize )
402  {
403  SCIP_CALL( SCIPreallocBufferArray(scip, &aggrdata->aggrrows, aggrrowsminsize) );
404  SCIP_CALL( SCIPreallocBufferArray(scip, &aggrdata->aggrrowscoef, aggrrowsminsize) );
405  }
406 
407  for( k = 0; k < ncolnonzeros; ++k )
408  {
409  /* ignore modifiable rows */
410  if( SCIProwIsModifiable(colrows[k]) )
411  continue;
412 
413  ++aggrdata->nbadvarsinrow[SCIProwGetLPPos(colrows[k])];
414  /* coverity[var_deref_op] */
415  aggrdata->aggrrows[aggrdata->naggrrows] = colrows[k];
416  aggrdata->aggrrowscoef[aggrdata->naggrrows] = colrowvals[k];
417  ++aggrdata->naggrrows;
418  }
419  }
420  }
421  }
422 
423  /* add sentinel entry at the end */
424  aggrdata->aggrrowsstart[aggrdata->nbounddistvars] = aggrdata->naggrrows;
425 
426  /* for each continous variable that is not at its bounds check if there is a
427  * row where it is the only such variable ("good" rows). In the array with the rows that are
428  * suitable for substituting this variable move the good rows to the beginning
429  * and store the number of good rows for each of the variables.
430  * If a variable has at least one good row, then it is a "better" variable and we make
431  * the value of the bounddistance for this variable negative, to mark it.
432  * Note that better variables are continous variables that are not at their bounds
433  * and can be projected out without introducing bad variables (by using a good row).
434  */
435  {
436  int beg;
437 
438  beg = aggrdata->aggrrowsstart[0];
439  for( i = 0; i < aggrdata->nbounddistvars; ++i )
440  {
441  int k;
442  int ngoodrows;
443  int end;
444 
445  end = aggrdata->aggrrowsstart[i + 1];
446  ngoodrows = 0;
447  for( k = beg; k < end; ++k )
448  {
449  /* coverity[var_deref_op] */
450  int lppos = SCIProwGetLPPos(aggrdata->aggrrows[k]);
451 
452  if( aggrdata->nbadvarsinrow[lppos] == 1 &&
453  SCIPisEQ(scip, SCIProwGetLhs(aggrdata->aggrrows[k]), SCIProwGetRhs(aggrdata->aggrrows[k])) )
454  {
455  int nextgoodrowpos = beg + ngoodrows;
456  if( k > nextgoodrowpos )
457  {
458  SCIPswapPointers((void**) (&aggrdata->aggrrows[k]), (void**) (&aggrdata->aggrrows[nextgoodrowpos]));
459  SCIPswapReals(&aggrdata->aggrrowscoef[k], &aggrdata->aggrrowscoef[nextgoodrowpos]);
460  }
461  ++ngoodrows;
462  }
463  }
464  if( ngoodrows > 0 )
465  {
466  aggrdata->bounddist[i] = -aggrdata->bounddist[i];
467  }
468  aggrdata->ngoodaggrrows[i] = ngoodrows;
469  beg = end;
470  }
471  }
472 
473  return SCIP_OKAY;
474 }
475 
476 /** free resources held in aggregation data */
477 static
479  SCIP* scip, /**< SCIP datastructure */
480  AGGREGATIONDATA* aggrdata /**< pointer to ggregation data */
481  )
482 {
483  SCIPaggrRowFree(scip, &aggrdata->aggrrow);
485  SCIPfreeBufferArrayNull(scip, &aggrdata->aggrrows);
486  SCIPfreeBufferArray(scip, &aggrdata->nbadvarsinrow);
487  SCIPfreeBufferArray(scip, &aggrdata->aggrrowsstart);
488  SCIPfreeBufferArray(scip, &aggrdata->ngoodaggrrows);
489  SCIPfreeBufferArray(scip, &aggrdata->bounddistinds);
490  SCIPfreeBufferArray(scip, &aggrdata->bounddist);
491 }
492 
493 /** retrieves the candidate rows for canceling out the given variable, also returns the number of "good" rows which are the
494  * rows stored at the first ngoodrows positions. A row is good if its continuous variables are all at their bounds, except
495  * maybe the given continuous variable (in probvaridx)
496  */
497 static
499  AGGREGATIONDATA* aggrdata, /**< pointer to ggregation data */
500  int probvaridx, /**< problem index of variables to retrieve candidates for */
501  SCIP_ROW*** rows, /**< pointer to store array to candidate rows */
502  SCIP_Real** rowvarcoefs, /**< pointer to store array of coefficients of given variable in the corresponding rows */
503  int* nrows, /**< pointer to return number of rows in returned arrays */
504  int* ngoodrows /**< pointer to return number of "good" rows in the returned arrays */
505  )
506 {
507  int aggrdataidx;
508 
509  if( !SCIPsortedvecFindInt(aggrdata->bounddistinds, probvaridx, aggrdata->nbounddistvars, &aggrdataidx) )
510  return FALSE;
511 
512  *rows = aggrdata->aggrrows + aggrdata->aggrrowsstart[aggrdataidx];
513  *nrows = aggrdata->aggrrowsstart[aggrdataidx + 1] - aggrdata->aggrrowsstart[aggrdataidx];
514  *rowvarcoefs = aggrdata->aggrrowscoef + aggrdata->aggrrowsstart[aggrdataidx];
515  *ngoodrows = aggrdata->ngoodaggrrows[aggrdataidx];
516 
517  return TRUE;
518 }
519 
520 /** find the bound distance value in the aggregation data struct for the given variable problem index */
521 static
523  AGGREGATIONDATA* aggrdata, /**< SCIP datastructure */
524  int probvaridx /**< problem index of variables to retrieve candidates for */
525  )
526 {
527  int aggrdataidx;
529  if( !SCIPsortedvecFindInt(aggrdata->bounddistinds, probvaridx, aggrdata->nbounddistvars, &aggrdataidx) )
530  return 0.0;
531 
532  return aggrdata->bounddist[aggrdataidx];
533 }
534 
535 /** Aggregates the next row suitable for cancelling out an active continuous variable.
536  *
537  * Equality rows that contain no other active continuous variables are preffered and apart from that
538  * the scores for the rows are used to determine which row is aggregated next
539  */
540 static
542  SCIP* scip, /**< SCIP data structure */
543  SCIP_SEPADATA* sepadata, /**< separator data */
544  SCIP_Real* rowlhsscores, /**< aggregation scores for left hand sides of row */
545  SCIP_Real* rowrhsscores, /**< aggregation scores for right hand sides of row */
546  AGGREGATIONDATA* aggrdata, /**< aggregation data */
547  SCIP_AGGRROW* aggrrow, /**< current aggregation row */
548  int* naggrs, /**< pointer to increase counter if real aggregation took place */
549  SCIP_Bool* success /**< pointer to return whether another row was added to the aggregation row */
550  )
551 {
552  int i;
553  int firstcontvar;
554  int* badvarinds;
555  SCIP_Real* badvarbddist;
556  int nbadvars;
557  SCIP_Real minbddist;
558  SCIP_ROW* bestrow;
559  SCIP_Real bestrowscore;
560  SCIP_Real aggrfac;
561  int bestrowside;
562  int ncontvars;
563  int nnz = SCIPaggrRowGetNNz(aggrrow);
564  int* inds = SCIPaggrRowGetInds(aggrrow);
565 
566  assert( success != NULL );
567  *success = FALSE;
568 
569  firstcontvar = SCIPgetNBinVars(scip) + SCIPgetNIntVars(scip);
570  ncontvars = SCIPgetNImplVars(scip) + SCIPgetNContVars(scip);
571  assert( firstcontvar + ncontvars == SCIPgetNVars(scip) );
572 
573  SCIP_CALL( SCIPallocBufferArray(scip, &badvarinds, MIN(ncontvars, nnz)) );
574  SCIP_CALL( SCIPallocBufferArray(scip, &badvarbddist, MIN(ncontvars, nnz)) );
575 
576  nbadvars = 0;
577 
578  for( i = 0; i < nnz; ++i )
579  {
580  SCIP_Real bounddist;
581 
582  /* only consider continuous variables */
583  if( inds[i] < firstcontvar )
584  continue;
585 
586  bounddist = aggrdataGetBoundDist(aggrdata, inds[i]);
587 
588  if( bounddist == 0.0 )
589  continue;
590 
591  badvarinds[nbadvars] = inds[i];
592  badvarbddist[nbadvars] = bounddist;
593  ++nbadvars;
594  }
595 
596  if( nbadvars == 0 )
597  goto TERMINATE;
598 
599  SCIPsortDownRealInt(badvarbddist, badvarinds, nbadvars);
600 
601  aggrfac = 0.0;
602  bestrowscore = 0.0;
603  bestrowside = 0;
604  minbddist = 0.0;
605  bestrow = NULL;
606 
607  /* because the "good" bad variables have a negative bound distance, they are at the end */
608  for( i = nbadvars - 1; i >= 0; --i )
609  {
610  int probvaridx;
611  SCIP_ROW** candrows;
612  SCIP_Real* candrowcoefs;
613  int nrows;
614  int ngoodrows;
615  int k;
616 
617  /* if the bound distance is not negative, there are no more good variables so stop */
618  if( badvarbddist[i] > 0.0 )
619  break;
620 
621  /* if no best row was found yet, this variable has the currently best bound distance */
622  if( aggrfac == 0.0 )
623  minbddist = -badvarbddist[i] * (1.0 - sepadata->aggrtol);
624 
625  /* if the bound distance of the current variable is smaller than the minimum bound distance stop looping */
626  if( -badvarbddist[i] < minbddist )
627  break;
628 
629  probvaridx = badvarinds[i];
630 
631  if( !getRowAggregationCandidates(aggrdata, probvaridx, &candrows, &candrowcoefs, &nrows, &ngoodrows) )
632  {
633  SCIPABORT();
634  }
635  assert(ngoodrows > 0); /* bounddistance was negative for this variable, so it should have good rows */
636 
637  for( k = 0; k < ngoodrows; ++k )
638  {
639  SCIP_Real rowaggrfac;
640  SCIP_Real rowscore;
641  int lppos;
642 
643  /* do not add rows twice */
644  if( SCIPaggrRowHasRowBeenAdded(aggrrow, candrows[k]) )
645  continue;
646 
647  rowaggrfac = - SCIPaggrRowGetProbvarValue(aggrrow, probvaridx) / candrowcoefs[k];
648 
649  /* if factor is too extreme skip this row */
650  if( SCIPisFeasZero(scip, rowaggrfac) || REALABS(rowaggrfac) > sepadata->maxrowfac )
651  continue;
652 
653  lppos = SCIProwGetLPPos(candrows[k]);
654 
655  /* row could be used and good rows are equalities, so ignore sidetype */
656  rowscore = MAX(rowlhsscores[lppos], rowrhsscores[lppos]);
657 
658  /* if this rows score is better than the currently best score, remember it */
659  if( aggrfac == 0.0 || rowscore > bestrowscore )
660  {
661  bestrow = candrows[k];
662  aggrfac = rowaggrfac;
663  bestrowscore = rowscore;
664  bestrowside = 0;
665  }
666  }
667  }
668 
669  /* found a row among the good rows, so aggregate it and stop */
670  if( aggrfac != 0.0 )
671  {
672  ++(*naggrs);
673  SCIP_CALL( SCIPaggrRowAddRow(scip, aggrrow, bestrow, aggrfac, bestrowside) );
674  SCIPaggrRowRemoveZeros(scip, aggrrow, success);
675  goto TERMINATE;
676  }
677 
678  for( i = 0; i < nbadvars; ++i )
679  {
680  int probvaridx;
681  SCIP_ROW** candrows;
682  SCIP_Real* candrowcoefs;
683  int nrows;
684  int ngoodrows;
685  int k;
686 
687  /* if the bound distance is negative, there are no more variables to be tested, so stop */
688  if( badvarbddist[i] < 0.0 )
689  break;
690 
691  /* if no best row was found yet, this variable has the currently best bound distance */
692  if( aggrfac == 0.0 )
693  minbddist = badvarbddist[i] * (1.0 - sepadata->aggrtol);
694 
695  /* if the bound distance of the current variable is smaller than the minimum bound distance stop looping */
696  if( badvarbddist[i] < minbddist )
697  break;
698 
699  probvaridx = badvarinds[i];
700 
701  if( !getRowAggregationCandidates(aggrdata, probvaridx, &candrows, &candrowcoefs, &nrows, &ngoodrows) )
702  {
703  SCIPABORT();
704  }
705 
706  /* bounddistance was positive for this variable, so it should not have good rows */
707  assert(ngoodrows == 0);
708 
709  for( k = 0; k < nrows; ++k )
710  {
711  SCIP_Real rowaggrfac;
712  SCIP_Real rowscore;
713  int rowside;
714  int lppos;
715 
716  /* do not add rows twice */
717  if( SCIPaggrRowHasRowBeenAdded(aggrrow, candrows[k]) )
718  continue;
719 
720  rowaggrfac = - SCIPaggrRowGetProbvarValue(aggrrow, probvaridx) / candrowcoefs[k];
721 
722  /* if factor is too extreme skip this row */
723  if( SCIPisFeasZero(scip, rowaggrfac) || REALABS(rowaggrfac) > sepadata->maxrowfac )
724  continue;
725 
726  /* row could be used, decide which side */
727  lppos = SCIProwGetLPPos(candrows[k]);
728 
729  /* either both or none of the rowscores are 0.0 so use the one which gives a positive slack */
730  if( (rowaggrfac < 0.0 && !SCIPisInfinity(scip, -SCIProwGetLhs(candrows[k]))) || SCIPisInfinity(scip, SCIProwGetRhs(candrows[k])) )
731  {
732  rowscore = rowlhsscores[lppos];
733  rowside = -1;
734  }
735  else
736  {
737  rowscore = rowrhsscores[lppos];
738  rowside = 1;
739  }
740 
741  /* if this rows score is better than the currently best score, remember it */
742  if( aggrfac == 0.0 || SCIPisGT(scip, rowscore, bestrowscore) ||
743  (SCIPisEQ(scip, rowscore, bestrowscore) && aggrdata->nbadvarsinrow[lppos] < aggrdata->nbadvarsinrow[SCIProwGetLPPos(bestrow)]) )
744  {
745  bestrow = candrows[k];
746  aggrfac = rowaggrfac;
747  bestrowscore = rowscore;
748  bestrowside = rowside;
749  }
750  }
751  }
752 
753  /* found a row so aggregate it */
754  if( aggrfac != 0.0 )
755  {
756  ++(*naggrs);
757  SCIP_CALL( SCIPaggrRowAddRow(scip, aggrrow, bestrow, aggrfac, bestrowside) );
758  SCIPaggrRowRemoveZeros(scip, aggrrow, success);
759  }
760 
761 TERMINATE:
762  SCIPfreeBufferArray(scip, &badvarbddist);
763  SCIPfreeBufferArray(scip, &badvarinds);
764 
765  return SCIP_OKAY;
766 }
767 
768 /** aggregates different single mixed integer constraints by taking linear combinations of the rows of the LP */
769 static
771  SCIP* scip, /**< SCIP data structure */
772  AGGREGATIONDATA* aggrdata, /**< pointer to aggregation data */
773  SCIP_SEPA* sepa, /**< separator */
774  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
775  SCIP_Bool allowlocal, /**< should local cuts be allowed */
776  SCIP_Real* rowlhsscores, /**< aggregation scores for left hand sides of row */
777  SCIP_Real* rowrhsscores, /**< aggregation scores for right hand sides of row */
778  int startrow, /**< index of row to start aggregation */
779  int maxaggrs, /**< maximal number of aggregations */
780  SCIP_Bool* wastried, /**< pointer to store whether the given startrow was actually tried */
781  SCIP_Bool* cutoff, /**< whether a cutoff has been detected */
782  int* cutinds, /**< buffer array to store temporarily cut */
783  SCIP_Real* cutcoefs, /**< buffer array to store temporarily cut */
784  SCIP_Bool negate, /**< should the start row be multiplied by -1 */
785  int* ncuts /**< pointer to count the number of generated cuts */
786  )
787 {
788  SCIP_SEPADATA* sepadata;
789  SCIP_ROW** rows;
790 
791  SCIP_Real startweight;
792  SCIP_Real startrowact;
793  int maxaggrnonzs;
794  int naggrs;
795  int nrows;
796  int maxtestdelta;
797 
798  SCIP_Real cutrhs;
799  SCIP_Real cutefficacy;
800 
801  assert(scip != NULL);
802  assert(sepa != NULL);
803  assert(rowlhsscores != NULL);
804  assert(rowrhsscores != NULL);
805  assert(wastried != NULL);
806  assert(cutoff != NULL);
807  assert(ncuts != NULL);
808 
809  sepadata = SCIPsepaGetData(sepa);
810  assert(sepadata != NULL);
811 
812  *cutoff = FALSE;
813  *wastried = FALSE;
814 
815  SCIP_CALL( SCIPgetLPRowsData(scip, &rows, &nrows) );
816  assert(nrows == 0 || rows != NULL);
817  assert(0 <= startrow && startrow < nrows);
818 
819  SCIPdebugMsg(scip, "start c-MIR aggregation with row <%s> (%d/%d)\n", SCIProwGetName(rows[startrow]), startrow, nrows);
820 
821  /* calculate maximal number of non-zeros in aggregated row */
822  maxaggrnonzs = (int)(sepadata->maxaggdensity * SCIPgetNLPCols(scip)) + sepadata->densityoffset;
823 
824  startrowact = SCIPgetRowSolActivity(scip, rows[startrow], sol);
825 
826  if( startrowact <= 0.5 * SCIProwGetLhs(rows[startrow]) + 0.5 * SCIProwGetRhs(rows[startrow]) )
827  startweight = -1.0;
828  else
829  startweight = 1.0;
830 
831  maxtestdelta = sepadata->maxtestdelta == -1 ? INT_MAX : sepadata->maxtestdelta;
832 
833  /* add start row to the initially empty aggregation row (aggrrow) */
834  SCIP_CALL( SCIPaggrRowAddRow(scip, aggrdata->aggrrow, rows[startrow], negate ? -startweight : startweight, 0) );
835 
836  /* try to generate cut from the current aggregated row; add cut if found, otherwise add another row to aggrrow
837  * in order to get rid of a continuous variable
838  */
839  naggrs = 0;
840  while( naggrs <= maxaggrs )
841  {
842  int cutrank;
843  int cutnnz;
844  SCIP_Bool aggrsuccess;
845  SCIP_Bool cmirsuccess;
846  SCIP_Bool cmircutislocal;
847  SCIP_Bool flowcoversuccess;
848  SCIP_Real flowcoverefficacy;
849  SCIP_Bool flowcovercutislocal;
850  SCIP_ROW* cut = NULL;
851 
852  *wastried = TRUE;
853 
854  /* Step 1:
855  * try to generate a MIR cut out of the current aggregated row
856  */
857 
858  flowcoverefficacy = -SCIPinfinity(scip);
859 
860  if( sepadata->sepflowcover )
861  {
862  SCIP_CALL( SCIPcalcFlowCover(scip, sol, POSTPROCESS, BOUNDSWITCH, allowlocal, aggrdata->aggrrow,
863  cutcoefs, &cutrhs, cutinds, &cutnnz, &flowcoverefficacy, &cutrank, &flowcovercutislocal, &flowcoversuccess) );
864  }
865  else
866  {
867  flowcoversuccess = FALSE;
868  }
869 
870  cutefficacy = flowcoverefficacy;
871 
872  if( sepadata->sepcmir )
873  {
874  SCIP_CALL( SCIPcutGenerationHeuristicCMIR(scip, sol, POSTPROCESS, BOUNDSWITCH, USEVBDS, allowlocal, maxtestdelta, NULL, NULL, MINFRAC, MAXFRAC,
875  aggrdata->aggrrow, cutcoefs, &cutrhs, cutinds, &cutnnz, &cutefficacy, &cutrank, &cmircutislocal, &cmirsuccess) );
876  }
877  else
878  {
879  cmirsuccess = FALSE;
880  }
881 
882  if( cmirsuccess )
883  {
884  SCIP_CALL( addCut(scip, sol, sepadata->cmir, FALSE, cutcoefs, cutinds, cutnnz, cutrhs, cutefficacy, cmircutislocal,
885  sepadata->dynamiccuts, cutrank, "cmir", cutoff, ncuts, &cut) ); /*lint !e644*/
886  }
887  else if ( flowcoversuccess )
888  {
889  /* cppcheck-suppress uninitvar */
890  SCIP_CALL( addCut(scip, sol, sepadata->flowcover, FALSE, cutcoefs, cutinds, cutnnz, cutrhs, cutefficacy, flowcovercutislocal,
891  sepadata->dynamiccuts, cutrank, "flowcover", cutoff, ncuts, &cut) ); /*lint !e644*/
892  }
893 
894  if ( *cutoff )
895  {
896  if( cut != NULL )
897  {
898  SCIP_CALL( SCIPreleaseRow(scip, &cut) );
899  }
900  break;
901  }
902 
903  /* if the cut was successfully added, decrease the score of the rows used in the aggregation and clean the aggregation
904  * row (and call this function again with a different start row for aggregation)
905  */
906  if( cut != NULL )
907  {
908  int* rowinds;
909  int i;
910 
911  rowinds = SCIPaggrRowGetRowInds(aggrdata->aggrrow);
912  nrows = SCIPaggrRowGetNRows(aggrdata->aggrrow);
913 
914  /* decrease row score of used rows slightly */
915  for( i = 0; i < nrows; ++i )
916  {
917  SCIP_Real fac = 1.0 - 0.999 * SCIProwGetParallelism(rows[rowinds[i]], cut, 'e');
918 
919  rowlhsscores[rowinds[i]] *= fac;
920  rowrhsscores[rowinds[i]] *= fac;
921  }
922 
923  SCIP_CALL( SCIPreleaseRow(scip, &cut) );
924 
925  SCIPdebugMsg(scip, " -> abort aggregation: cut found\n");
926  break;
927  }
928 
929  /* Step 2:
930  * aggregate an additional row in order to remove a continuous variable
931  */
932 
933  /* abort, if we reached the maximal number of aggregations */
934  if( naggrs == maxaggrs )
935  {
936  SCIPdebugMsg(scip, " -> abort aggregation: maximal number of aggregations reached\n");
937  break;
938  }
939 
940  SCIP_CALL( aggregateNextRow(scip, sepadata, rowlhsscores, rowrhsscores, aggrdata, aggrdata->aggrrow,
941  &naggrs, &aggrsuccess) );
942 
943  /* no suitable aggregation was found or number of non-zeros is now too large so abort */
944  if( ! aggrsuccess || SCIPaggrRowGetNNz(aggrdata->aggrrow) > maxaggrnonzs || SCIPaggrRowGetNNz(aggrdata->aggrrow) == 0 )
945  {
946  break;
947  }
948 
949  SCIPdebugMsg(scip, " -> current aggregation has %d/%d nonzeros and consists of %d/%d rows\n",
950  SCIPaggrRowGetNNz(aggrdata->aggrrow), maxaggrnonzs, naggrs, maxaggrs);
951  }
952 
953  SCIPaggrRowClear(aggrdata->aggrrow);
954 
955  return SCIP_OKAY;
956 }
957 
958 /** gives an estimate of how much the activity of this row is affected by fractionality in the current solution */
959 static
961  SCIP_ROW* row, /**< the LP row */
962  SCIP_Real* fractionalities /**< array of fractionalities for each variable */
963  )
964 {
965  int nlpnonz;
966  int i;
967  SCIP_COL** cols;
968  SCIP_Real* vals;
969  SCIP_Real fracsum = 0.0;
970 
971  cols = SCIProwGetCols(row);
972  vals = SCIProwGetVals(row);
973  nlpnonz = SCIProwGetNLPNonz(row);
974 
975  for( i = 0; i < nlpnonz; ++i )
976  {
977  SCIP_VAR* var = SCIPcolGetVar(cols[i]);
978  fracsum += REALABS(vals[i] * fractionalities[SCIPvarGetProbindex(var)]);
979  }
980 
981  return fracsum;
982 }
983 
984 /** searches and adds c-MIR cuts that separate the given primal solution */
985 static
987  SCIP* scip, /**< SCIP data structure */
988  SCIP_SEPA* sepa, /**< the c-MIR separator */
989  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
990  SCIP_Bool allowlocal, /**< should local cuts be allowed */
991  SCIP_RESULT* result /**< pointer to store the result */
992  )
993 {
994  AGGREGATIONDATA aggrdata;
995  SCIP_SEPADATA* sepadata;
996  SCIP_VAR** vars;
997  SCIP_Real* varsolvals;
998  SCIP_Real* bestcontlbs;
999  SCIP_Real* bestcontubs;
1000  SCIP_Real* fractionalities;
1001  SCIP_ROW** rows;
1002  SCIP_Real* rowlhsscores;
1003  SCIP_Real* rowrhsscores;
1004  SCIP_Real* rowscores;
1005  int* roworder;
1006  SCIP_Real maxslack;
1007  SCIP_Bool cutoff = FALSE;
1008  int nvars;
1009  int nintvars;
1010  int ncontvars;
1011  int nrows;
1012  int nnonzrows;
1013  int zerorows;
1014  int ntries;
1015  int nfails;
1016  int depth;
1017  int ncalls;
1018  int maxtries;
1019  int maxfails;
1020  int maxaggrs;
1021  int maxsepacuts;
1022  int ncuts;
1023  int r;
1024  int v;
1025 
1026  int* cutinds;
1027  SCIP_Real* cutcoefs;
1028 
1029  assert(result != NULL);
1030  assert(*result == SCIP_DIDNOTRUN);
1031 
1032  sepadata = SCIPsepaGetData(sepa);
1033  assert(sepadata != NULL);
1034 
1035  depth = SCIPgetDepth(scip);
1036  ncalls = SCIPsepaGetNCallsAtNode(sepa);
1037 
1038  /* only call the cmir cut separator a given number of times at each node */
1039  if( (depth == 0 && sepadata->maxroundsroot >= 0 && ncalls >= sepadata->maxroundsroot)
1040  || (depth > 0 && sepadata->maxrounds >= 0 && ncalls >= sepadata->maxrounds) )
1041  return SCIP_OKAY;
1042 
1043  /* check which cuts should be separated */
1044  {
1045  int cmirfreq;
1046  int flowcoverfreq;
1047 
1048  cmirfreq = SCIPsepaGetFreq(sepadata->cmir);
1049  flowcoverfreq = SCIPsepaGetFreq(sepadata->flowcover);
1050 
1051  sepadata->sepcmir = cmirfreq > 0 ? (depth % cmirfreq) == 0 : cmirfreq == depth;
1052  sepadata->sepflowcover = flowcoverfreq > 0 ? (depth % flowcoverfreq) == 0 : flowcoverfreq == depth;
1053  }
1054 
1055  if( ! sepadata->sepcmir && ! sepadata->sepflowcover )
1056  return SCIP_OKAY;
1057 
1058  /* get all rows and number of columns */
1059  SCIP_CALL( SCIPgetLPRowsData(scip, &rows, &nrows) );
1060  assert(nrows == 0 || rows != NULL);
1061 
1062  /* nothing to do, if LP is empty */
1063  if( nrows == 0 )
1064  return SCIP_OKAY;
1065 
1066  /* check whether SCIP was stopped in the meantime */
1067  if( SCIPisStopped(scip) )
1068  return SCIP_OKAY;
1069 
1070  /* get active problem variables */
1071  vars = SCIPgetVars(scip);
1072  nvars = SCIPgetNVars(scip);
1073  ncontvars = SCIPgetNContVars(scip);
1074 #ifdef IMPLINTSARECONT
1075  ncontvars += SCIPgetNImplVars(scip); /* also aggregate out implicit integers */
1076 #endif
1077  nintvars = nvars - ncontvars;
1078  assert(nvars == 0 || vars != NULL);
1079 
1080  /* nothing to do, if problem has no variables */
1081  if( nvars == 0 )
1082  return SCIP_OKAY;
1083 
1084  SCIPdebugMsg(scip, "separating c-MIR cuts\n");
1085 
1086  *result = SCIP_DIDNOTFIND;
1087 
1088  /* get data structure */
1089  SCIP_CALL( SCIPallocBufferArray(scip, &rowlhsscores, nrows) );
1090  SCIP_CALL( SCIPallocBufferArray(scip, &rowrhsscores, nrows) );
1091  SCIP_CALL( SCIPallocBufferArray(scip, &rowscores, nrows) );
1092  SCIP_CALL( SCIPallocBufferArray(scip, &roworder, nrows) );
1093  SCIP_CALL( SCIPallocBufferArray(scip, &varsolvals, nvars) );
1094  SCIP_CALL( SCIPallocBufferArray(scip, &bestcontlbs, ncontvars) );
1095  SCIP_CALL( SCIPallocBufferArray(scip, &bestcontubs, ncontvars) );
1096  SCIP_CALL( SCIPallocBufferArray(scip, &fractionalities, nvars) );
1097  SCIP_CALL( SCIPallocBufferArray(scip, &cutinds, nvars) );
1098  SCIP_CALL( SCIPallocBufferArray(scip, &cutcoefs, nvars) );
1099 
1100  /* get the solution values for all active variables */
1101  SCIP_CALL( SCIPgetSolVals(scip, sol, nvars, vars, varsolvals) );
1102 
1103  /* calculate the fractionality of the integer variables in the current solution */
1104  for( v = 0; v < nintvars; ++v )
1105  {
1106  fractionalities[v] = SCIPfeasFrac(scip, varsolvals[v]);
1107  fractionalities[v] = MIN(fractionalities[v], 1.0 - fractionalities[v]);
1108  }
1109 
1110  /* calculate the fractionality of the continuous variables in the current solution;
1111  * The fractionality of a continuous variable x is defined to be a * f_y,
1112  * if there is a variable bound x <= a * y + c where f_y is the fractionality of y
1113  * and in the current solution the variable bound has no slack.
1114  */
1115  for( ; v < nvars; ++v )
1116  {
1117  SCIP_VAR** vlbvars;
1118  SCIP_VAR** vubvars;
1119  SCIP_Real* vlbcoefs;
1120  SCIP_Real* vubcoefs;
1121  SCIP_Real closestvlb;
1122  SCIP_Real closestvub;
1123  int closestvlbidx;
1124  int closestvubidx;
1125 
1126  SCIP_CALL( SCIPgetVarClosestVlb(scip, vars[v], sol, &closestvlb, &closestvlbidx) );
1127  SCIP_CALL( SCIPgetVarClosestVub(scip, vars[v], sol, &closestvub, &closestvubidx) );
1128 
1129  vlbvars = SCIPvarGetVlbVars(vars[v]);
1130  vubvars = SCIPvarGetVubVars(vars[v]);
1131  vlbcoefs = SCIPvarGetVlbCoefs(vars[v]);
1132  vubcoefs = SCIPvarGetVubCoefs(vars[v]);
1133 
1134  fractionalities[v] = 0.0;
1135  if( closestvlbidx != -1 && SCIPisEQ(scip, varsolvals[v], closestvlb) )
1136  {
1137  int vlbvarprobidx = SCIPvarGetProbindex(vlbvars[closestvlbidx]);
1138  SCIP_Real frac = SCIPfeasFrac(scip, varsolvals[vlbvarprobidx]);
1139 
1140  if( frac < 0.0 )
1141  frac = 0.0;
1142  assert(frac >= 0.0 && frac < 1.0);
1143  frac = MIN(frac, 1.0 - frac) * vlbcoefs[closestvlbidx];
1144  fractionalities[v] += frac;
1145  }
1146 
1147  if( closestvubidx != -1 && SCIPisEQ(scip, varsolvals[v], closestvub) )
1148  {
1149  int vubvarprobidx = SCIPvarGetProbindex(vubvars[closestvubidx]);
1150  SCIP_Real frac = SCIPfeasFrac(scip, varsolvals[vubvarprobidx]);
1151 
1152  if( frac < 0.0 )
1153  frac = 0.0;
1154  assert(frac >= 0.0 && frac < 1.0);
1155  frac = MIN(frac, 1.0 - frac) * vubcoefs[closestvubidx];
1156  fractionalities[v] += frac;
1157  }
1158  }
1159 
1160  /* get the maximal number of cuts allowed in a separation round */
1161  if( depth == 0 )
1162  {
1163  maxtries = sepadata->maxtriesroot;
1164  maxfails = sepadata->maxfailsroot;
1165  maxaggrs = sepadata->maxaggrsroot;
1166  maxsepacuts = sepadata->maxsepacutsroot;
1167  maxslack = sepadata->maxslackroot;
1168  }
1169  else
1170  {
1171  maxtries = sepadata->maxtries;
1172  maxfails = sepadata->maxfails;
1173  maxaggrs = sepadata->maxaggrs;
1174  maxsepacuts = sepadata->maxsepacuts;
1175  maxslack = sepadata->maxslack;
1176  }
1177 
1178  /* calculate aggregation scores for both sides of all rows, and sort rows by decreasing maximal score
1179  * TODO: document score definition */
1180 
1181  /* count the number of non-zero rows and zero rows. these values are used for the sorting of the rowscores.
1182  * only the non-zero rows need to be sorted. */
1183  nnonzrows = 0;
1184  zerorows = 0;
1185  for( r = 0; r < nrows; r++ )
1186  {
1187  int nnonz;
1188  int i;
1189 
1190  assert(SCIProwGetLPPos(rows[r]) == r);
1191 
1192  nnonz = SCIProwGetNLPNonz(rows[r]);
1193  if( nnonz == 0 )
1194  {
1195  /* ignore empty rows */
1196  rowlhsscores[r] = 0.0;
1197  rowrhsscores[r] = 0.0;
1198 
1199  /* add the row number to the back of roworder for zero rows */
1200  zerorows++;
1201  rowscores[r] = 0.0;
1202  roworder[nrows - zerorows] = r;
1203  }
1204  else
1205  {
1206  SCIP_Real activity;
1207  SCIP_Real lhs;
1208  SCIP_Real rhs;
1209  SCIP_Real dualsol;
1210  SCIP_Real dualscore;
1211  SCIP_Real rowdensity;
1212  SCIP_Real rownorm;
1213  SCIP_Real slack;
1214  SCIP_Real fracact;
1215  SCIP_Real fracscore;
1216  SCIP_Real objnorm;
1217 
1218  objnorm = SCIPgetObjNorm(scip);
1219  objnorm = MAX(objnorm, 1.0);
1220 
1221  fracact = getRowFracActivity(rows[r], fractionalities);
1222  dualsol = (sol == NULL ? SCIProwGetDualsol(rows[r]) : 1.0);
1223  activity = SCIPgetRowSolActivity(scip, rows[r], sol);
1224  lhs = SCIProwGetLhs(rows[r]);
1225  rhs = SCIProwGetRhs(rows[r]);
1226  rownorm = SCIProwGetNorm(rows[r]);
1227  rownorm = MAX(rownorm, 0.1);
1228  rowdensity = (SCIP_Real)(nnonz - sepadata->densityoffset)/(SCIP_Real)nvars;
1229  assert(SCIPisPositive(scip, rownorm));
1230  fracscore = fracact / rownorm;
1231 
1232  slack = (activity - lhs)/rownorm;
1233  dualscore = MAX(fracscore * dualsol/objnorm, 0.0001);
1234  if( !SCIPisInfinity(scip, -lhs) && SCIPisLE(scip, slack, maxslack)
1235  && (allowlocal || !SCIProwIsLocal(rows[r])) /*lint !e506 !e774*/
1236  && rowdensity <= sepadata->maxrowdensity
1237  && rowdensity <= sepadata->maxaggdensity ) /*lint !e774*/
1238  {
1239  rowlhsscores[r] = dualscore + sepadata->densityscore * (1.0-rowdensity) + sepadata->slackscore * MAX(1.0 - slack, 0.0);
1240  assert(rowlhsscores[r] > 0.0);
1241  }
1242  else
1243  rowlhsscores[r] = 0.0;
1244 
1245  slack = (rhs - activity)/rownorm;
1246  dualscore = MAX(-fracscore * dualsol/objnorm, 0.0001);
1247  if( !SCIPisInfinity(scip, rhs) && SCIPisLE(scip, slack, maxslack)
1248  && (allowlocal || !SCIProwIsLocal(rows[r])) /*lint !e506 !e774*/
1249  && rowdensity <= sepadata->maxrowdensity
1250  && rowdensity <= sepadata->maxaggdensity ) /*lint !e774*/
1251  {
1252  rowrhsscores[r] = dualscore + sepadata->densityscore * (1.0-rowdensity) + sepadata->slackscore * MAX(1.0 - slack, 0.0);
1253  assert(rowrhsscores[r] > 0.0);
1254  }
1255  else
1256  rowrhsscores[r] = 0.0;
1257 
1258  /* for the row order only use the fractionality score since it best indicates how likely it is to find a cut */
1259  rowscores[r] = fracscore;
1260  if( rowscores[r] == 0.0 )
1261  {
1262  /* add the row number to the back of roworder for zero rows */
1263  zerorows++;
1264  roworder[nrows - zerorows] = r;
1265  }
1266  else
1267  {
1268  /* insert the row number in the correct position of roworder */
1269  for( i = nnonzrows; i > 0 && rowscores[r] > rowscores[roworder[i - 1]]; --i )
1270  roworder[i] = roworder[i - 1];
1271  roworder[i] = r;
1272 
1273  nnonzrows++;
1274  }
1275  }
1276 
1277  SCIPdebugMsg(scip, " -> row %d <%s>: lhsscore=%g rhsscore=%g maxscore=%g\n", r, SCIProwGetName(rows[r]),
1278  rowlhsscores[r], rowrhsscores[r], rowscores[r]);
1279  }
1280  assert(nrows == nnonzrows + zerorows);
1281 
1282  /* calculate the data required for performing the row aggregation */
1283  SCIP_CALL( setupAggregationData(scip, sol, allowlocal, &aggrdata) );
1284 
1285  ncuts = 0;
1286  if( maxtries < 0 )
1287  maxtries = INT_MAX;
1288  if( maxfails < 0 )
1289  maxfails = INT_MAX;
1290  else if( depth == 0 && 2 * SCIPgetNSepaRounds(scip) < maxfails )
1291  maxfails += maxfails - 2 * SCIPgetNSepaRounds(scip); /* allow up to double as many fails in early separounds of root node */
1292 
1293  /* start aggregation heuristic for each row in the LP and generate resulting cuts */
1294  ntries = 0;
1295  nfails = 0;
1296  for( r = 0; r < nnonzrows && ntries < maxtries && ncuts < maxsepacuts && !SCIPisStopped(scip); r++ )
1297  {
1298  SCIP_Bool wastried;
1299  int oldncuts;
1300 
1301  oldncuts = ncuts;
1302  SCIP_CALL( aggregation(scip, &aggrdata, sepa, sol, allowlocal, rowlhsscores, rowrhsscores,
1303  roworder[r], maxaggrs, &wastried, &cutoff, cutinds, cutcoefs, FALSE, &ncuts) );
1304 
1305  /* if trynegscaling is true we start the aggregation heuristic again for this row, but multiply it by -1 first.
1306  * This is done by calling the aggregation function with the parameter negate equal to TRUE
1307  */
1308  if( sepadata->trynegscaling && !cutoff )
1309  {
1310  SCIP_CALL( aggregation(scip, &aggrdata, sepa, sol, allowlocal, rowlhsscores, rowrhsscores,
1311  roworder[r], maxaggrs, &wastried, &cutoff, cutinds, cutcoefs, TRUE, &ncuts) );
1312  }
1313 
1314  if ( cutoff )
1315  break;
1316 
1317  if( !wastried )
1318  {
1319  continue;
1320  }
1321  ntries++;
1322 
1323  if( ncuts == oldncuts )
1324  {
1325  nfails++;
1326  if( nfails >= maxfails )
1327  {
1328  break;
1329  }
1330  }
1331  else
1332  {
1333  nfails = 0;
1334  }
1335  }
1336 
1337  /* free data structure */
1338  destroyAggregationData(scip, &aggrdata);
1339  SCIPfreeBufferArray(scip, &cutcoefs);
1340  SCIPfreeBufferArray(scip, &cutinds);
1341  SCIPfreeBufferArray(scip, &fractionalities);
1342  SCIPfreeBufferArray(scip, &bestcontubs);
1343  SCIPfreeBufferArray(scip, &bestcontlbs);
1344  SCIPfreeBufferArray(scip, &varsolvals);
1345  SCIPfreeBufferArray(scip, &roworder);
1346  SCIPfreeBufferArray(scip, &rowscores);
1347  SCIPfreeBufferArray(scip, &rowrhsscores);
1348  SCIPfreeBufferArray(scip, &rowlhsscores);
1349 
1350  if ( cutoff )
1351  *result = SCIP_CUTOFF;
1352  else if ( ncuts > 0 )
1353  *result = SCIP_SEPARATED;
1354 
1355  return SCIP_OKAY;
1356 }
1357 
1358 /*
1359  * Callback methods of separator
1360  */
1361 
1362 /** copy method for separator plugins (called when SCIP copies plugins) */
1363 static
1364 SCIP_DECL_SEPACOPY(sepaCopyAggregation)
1365 { /*lint --e{715}*/
1366  assert(scip != NULL);
1367  assert(sepa != NULL);
1368  assert(strcmp(SCIPsepaGetName(sepa), SEPA_NAME) == 0);
1369 
1370  /* call inclusion method of constraint handler */
1372 
1373  return SCIP_OKAY;
1374 }
1375 
1376 /** destructor of separator to free user data (called when SCIP is exiting) */
1377 static
1378 SCIP_DECL_SEPAFREE(sepaFreeAggregation)
1379 { /*lint --e{715}*/
1380  SCIP_SEPADATA* sepadata;
1381 
1382  /* free separator data */
1383  sepadata = SCIPsepaGetData(sepa);
1384  assert(sepadata != NULL);
1385 
1386  SCIPfreeBlockMemory(scip, &sepadata);
1387 
1388  SCIPsepaSetData(sepa, NULL);
1389 
1390  return SCIP_OKAY;
1391 }
1392 
1393 /** LP solution separation method of separator */
1394 static
1395 SCIP_DECL_SEPAEXECLP(sepaExeclpAggregation)
1396 { /*lint --e{715}*/
1397  assert( result != NULL );
1398 
1399  *result = SCIP_DIDNOTRUN;
1400 
1401  /* only call separator, if we are not close to terminating */
1402  if( SCIPisStopped(scip) )
1403  return SCIP_OKAY;
1404 
1405  /* only call separator, if an optimal LP solution is at hand */
1407  return SCIP_OKAY;
1408 
1409  /* only call separator, if there are fractional variables */
1410  if( SCIPgetNLPBranchCands(scip) == 0 )
1411  return SCIP_OKAY;
1412 
1413  SCIP_CALL( separateCuts(scip, sepa, NULL, allowlocal, result) );
1414 
1415  return SCIP_OKAY;
1416 }
1417 
1418 /** arbitrary primal solution separation method of separator */
1419 static
1420 SCIP_DECL_SEPAEXECSOL(sepaExecsolAggregation)
1421 { /*lint --e{715}*/
1422  assert( result != NULL );
1423 
1424  *result = SCIP_DIDNOTRUN;
1425 
1426  SCIP_CALL( separateCuts(scip, sepa, sol, allowlocal, result) );
1427 
1428  return SCIP_OKAY;
1429 }
1430 
1431 /** LP solution separation method of dummy separator */
1432 static
1433 SCIP_DECL_SEPAEXECLP(sepaExeclpDummy)
1434 { /*lint --e{715}*/
1435  assert( result != NULL );
1436 
1437  *result = SCIP_DIDNOTRUN;
1438 
1439  return SCIP_OKAY;
1440 }
1441 
1442 /** arbitrary primal solution separation method of dummy separator */
1443 static
1444 SCIP_DECL_SEPAEXECSOL(sepaExecsolDummy)
1445 { /*lint --e{715}*/
1446  assert( result != NULL );
1447 
1448  *result = SCIP_DIDNOTRUN;
1449 
1450  return SCIP_OKAY;
1451 }
1452 
1453 /*
1454  * separator specific interface methods
1455  */
1456 
1457 /** creates the cmir separator and includes it in SCIP */
1459  SCIP* scip /**< SCIP data structure */
1460  )
1461 {
1462  SCIP_SEPADATA* sepadata;
1463  SCIP_SEPA* sepa;
1465  /* create cmir separator data */
1466  SCIP_CALL( SCIPallocBlockMemory(scip, &sepadata) );
1467 
1468  /* include dummy separators */
1469  SCIP_CALL( SCIPincludeSepaBasic(scip, &sepadata->flowcover, "flowcover", "separator for flowcover cuts", -100000, SEPA_FREQ, 0.0,
1470  SEPA_USESSUBSCIP, FALSE, sepaExeclpDummy, sepaExecsolDummy, NULL) );
1471 
1472  assert(sepadata->flowcover != NULL);
1473 
1474  SCIP_CALL( SCIPincludeSepaBasic(scip, &sepadata->cmir, "cmir", "separator for cmir cuts", -100000, SEPA_FREQ, 0.0,
1475  SEPA_USESSUBSCIP, FALSE, sepaExeclpDummy, sepaExecsolDummy, NULL) );
1476 
1477  assert(sepadata->cmir != NULL);
1478 
1479  /* include separator */
1482  sepaExeclpAggregation, sepaExecsolAggregation,
1483  sepadata) );
1484 
1485  assert(sepa != NULL);
1486 
1487  /* set non-NULL pointers to callback methods */
1488  SCIP_CALL( SCIPsetSepaCopy(scip, sepa, sepaCopyAggregation) );
1489  SCIP_CALL( SCIPsetSepaFree(scip, sepa, sepaFreeAggregation) );
1490 
1491  /* add cmir separator parameters */
1492  SCIP_CALL( SCIPaddIntParam(scip,
1493  "separating/" SEPA_NAME "/maxrounds",
1494  "maximal number of cmir separation rounds per node (-1: unlimited)",
1495  &sepadata->maxrounds, FALSE, DEFAULT_MAXROUNDS, -1, INT_MAX, NULL, NULL) );
1496  SCIP_CALL( SCIPaddIntParam(scip,
1497  "separating/" SEPA_NAME "/maxroundsroot",
1498  "maximal number of cmir separation rounds in the root node (-1: unlimited)",
1499  &sepadata->maxroundsroot, FALSE, DEFAULT_MAXROUNDSROOT, -1, INT_MAX, NULL, NULL) );
1500  SCIP_CALL( SCIPaddIntParam(scip,
1501  "separating/" SEPA_NAME "/maxtries",
1502  "maximal number of rows to start aggregation with per separation round (-1: unlimited)",
1503  &sepadata->maxtries, TRUE, DEFAULT_MAXTRIES, -1, INT_MAX, NULL, NULL) );
1504  SCIP_CALL( SCIPaddIntParam(scip,
1505  "separating/" SEPA_NAME "/maxtriesroot",
1506  "maximal number of rows to start aggregation with per separation round in the root node (-1: unlimited)",
1507  &sepadata->maxtriesroot, TRUE, DEFAULT_MAXTRIESROOT, -1, INT_MAX, NULL, NULL) );
1508  SCIP_CALL( SCIPaddIntParam(scip,
1509  "separating/" SEPA_NAME "/maxfails",
1510  "maximal number of consecutive unsuccessful aggregation tries (-1: unlimited)",
1511  &sepadata->maxfails, TRUE, DEFAULT_MAXFAILS, -1, INT_MAX, NULL, NULL) );
1512  SCIP_CALL( SCIPaddIntParam(scip,
1513  "separating/" SEPA_NAME "/maxfailsroot",
1514  "maximal number of consecutive unsuccessful aggregation tries in the root node (-1: unlimited)",
1515  &sepadata->maxfailsroot, TRUE, DEFAULT_MAXFAILSROOT, -1, INT_MAX, NULL, NULL) );
1516  SCIP_CALL( SCIPaddIntParam(scip,
1517  "separating/" SEPA_NAME "/maxaggrs",
1518  "maximal number of aggregations for each row per separation round",
1519  &sepadata->maxaggrs, TRUE, DEFAULT_MAXAGGRS, 0, INT_MAX, NULL, NULL) );
1520  SCIP_CALL( SCIPaddIntParam(scip,
1521  "separating/" SEPA_NAME "/maxaggrsroot",
1522  "maximal number of aggregations for each row per separation round in the root node",
1523  &sepadata->maxaggrsroot, TRUE, DEFAULT_MAXAGGRSROOT, 0, INT_MAX, NULL, NULL) );
1524  SCIP_CALL( SCIPaddIntParam(scip,
1525  "separating/" SEPA_NAME "/maxsepacuts",
1526  "maximal number of cmir cuts separated per separation round",
1527  &sepadata->maxsepacuts, FALSE, DEFAULT_MAXSEPACUTS, 0, INT_MAX, NULL, NULL) );
1528  SCIP_CALL( SCIPaddIntParam(scip,
1529  "separating/" SEPA_NAME "/maxsepacutsroot",
1530  "maximal number of cmir cuts separated per separation round in the root node",
1531  &sepadata->maxsepacutsroot, FALSE, DEFAULT_MAXSEPACUTSROOT, 0, INT_MAX, NULL, NULL) );
1533  "separating/" SEPA_NAME "/maxslack",
1534  "maximal slack of rows to be used in aggregation",
1535  &sepadata->maxslack, TRUE, DEFAULT_MAXSLACK, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1537  "separating/" SEPA_NAME "/maxslackroot",
1538  "maximal slack of rows to be used in aggregation in the root node",
1539  &sepadata->maxslackroot, TRUE, DEFAULT_MAXSLACKROOT, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1541  "separating/" SEPA_NAME "/densityscore",
1542  "weight of row density in the aggregation scoring of the rows",
1543  &sepadata->densityscore, TRUE, DEFAULT_DENSITYSCORE, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1545  "separating/" SEPA_NAME "/slackscore",
1546  "weight of slack in the aggregation scoring of the rows",
1547  &sepadata->slackscore, TRUE, DEFAULT_SLACKSCORE, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1549  "separating/" SEPA_NAME "/maxaggdensity",
1550  "maximal density of aggregated row",
1551  &sepadata->maxaggdensity, TRUE, DEFAULT_MAXAGGDENSITY, 0.0, 1.0, NULL, NULL) );
1553  "separating/" SEPA_NAME "/maxrowdensity",
1554  "maximal density of row to be used in aggregation",
1555  &sepadata->maxrowdensity, TRUE, DEFAULT_MAXROWDENSITY, 0.0, 1.0, NULL, NULL) );
1556  SCIP_CALL( SCIPaddIntParam(scip,
1557  "separating/" SEPA_NAME "/densityoffset",
1558  "additional number of variables allowed in row on top of density",
1559  &sepadata->densityoffset, TRUE, DEFAULT_DENSITYOFFSET, 0, INT_MAX, NULL, NULL) );
1561  "separating/" SEPA_NAME "/maxrowfac",
1562  "maximal row aggregation factor",
1563  &sepadata->maxrowfac, TRUE, DEFAULT_MAXROWFAC, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1564  SCIP_CALL( SCIPaddIntParam(scip,
1565  "separating/" SEPA_NAME "/maxtestdelta",
1566  "maximal number of different deltas to try (-1: unlimited)",
1567  &sepadata->maxtestdelta, TRUE, DEFAULT_MAXTESTDELTA, -1, INT_MAX, NULL, NULL) );
1569  "separating/" SEPA_NAME "/aggrtol",
1570  "tolerance for bound distances used to select continuous variable in current aggregated constraint to be eliminated",
1571  &sepadata->aggrtol, TRUE, DEFAULT_AGGRTOL, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1573  "separating/" SEPA_NAME "/trynegscaling",
1574  "should negative values also be tested in scaling?",
1575  &sepadata->trynegscaling, TRUE, DEFAULT_TRYNEGSCALING, NULL, NULL) );
1577  "separating/" SEPA_NAME "/fixintegralrhs",
1578  "should an additional variable be complemented if f0 = 0?",
1579  &sepadata->fixintegralrhs, TRUE, DEFAULT_FIXINTEGRALRHS, NULL, NULL) );
1581  "separating/" SEPA_NAME "/dynamiccuts",
1582  "should generated cuts be removed from the LP if they are no longer tight?",
1583  &sepadata->dynamiccuts, FALSE, DEFAULT_DYNAMICCUTS, NULL, NULL) );
1584 
1585  return SCIP_OKAY;
1586 }
enum SCIP_Result SCIP_RESULT
Definition: type_result.h:52
#define DEFAULT_MAXAGGRS
static SCIP_RETCODE addCut(SCIP *scip, SCIP_SOL *sol, SCIP_SEPA *sepa, SCIP_Bool makeintegral, SCIP_Real *cutcoefs, int *cutinds, int cutnnz, SCIP_Real cutrhs, SCIP_Real cutefficacy, SCIP_Bool cutislocal, SCIP_Bool cutremovable, int cutrank, const char *cutclassname, SCIP_Bool *cutoff, int *ncuts, SCIP_ROW **thecut)
#define SEPA_MAXBOUNDDIST
int SCIPgetNIntVars(SCIP *scip)
Definition: scip_prob.c:2134
SCIP_Bool SCIPisFeasZero(SCIP *scip, SCIP_Real val)
#define MAKECONTINTEGRAL
#define DEFAULT_DENSITYSCORE
void SCIPaggrRowFree(SCIP *scip, SCIP_AGGRROW **aggrrow)
Definition: cuts.c:1581
int SCIPaggrRowGetNRows(SCIP_AGGRROW *aggrrow)
Definition: cuts.c:2295
#define DEFAULT_MAXFAILSROOT
SCIP_Real * SCIPvarGetVlbCoefs(SCIP_VAR *var)
Definition: var.c:17558
#define NULL
Definition: def.h:246
#define DEFAULT_MAXTESTDELTA
SCIP_RETCODE SCIPcacheRowExtensions(SCIP *scip, SCIP_ROW *row)
Definition: scip_lp.c:1547
public methods for SCIP parameter handling
SCIP_RETCODE SCIPaggrRowAddRow(SCIP *scip, SCIP_AGGRROW *aggrrow, SCIP_ROW *row, SCIP_Real weight, int sidetype)
Definition: cuts.c:1684
#define BOUNDSWITCH
public methods for memory management
static SCIP_DECL_SEPACOPY(sepaCopyAggregation)
SCIP_RETCODE SCIPflushRowExtensions(SCIP *scip, SCIP_ROW *row)
Definition: scip_lp.c:1570
SCIP_Real SCIPvarGetLbGlobal(SCIP_VAR *var)
Definition: var.c:17344
#define SCIP_MAXSTRLEN
Definition: def.h:267
#define DEFAULT_MAXROUNDSROOT
SCIP_Real * SCIPcolGetVals(SCIP_COL *col)
Definition: lp.c:16838
static SCIP_DECL_SEPAEXECSOL(sepaExecsolAggregation)
#define DEFAULT_MAXSLACKROOT
SCIP_RETCODE SCIPaddVarToRow(SCIP *scip, SCIP_ROW *row, SCIP_VAR *var, SCIP_Real val)
Definition: scip_lp.c:1607
int SCIProwGetNNonz(SCIP_ROW *row)
Definition: lp.c:16880
SCIP_Bool SCIPisPositive(SCIP *scip, SCIP_Real val)
SCIP_Real SCIPvarGetLbLocal(SCIP_VAR *var)
Definition: var.c:17400
#define DEFAULT_FIXINTEGRALRHS
const char * SCIProwGetName(SCIP_ROW *row)
Definition: lp.c:17018
int SCIProwGetNLPNonz(SCIP_ROW *row)
Definition: lp.c:16894
void SCIPswapPointers(void **pointer1, void **pointer2)
Definition: misc.c:9881
SCIP_RETCODE SCIPgetVarsData(SCIP *scip, SCIP_VAR ***vars, int *nvars, int *nbinvars, int *nintvars, int *nimplvars, int *ncontvars)
Definition: scip_prob.c:1918
SCIP_Real SCIProwGetLhs(SCIP_ROW *row)
Definition: lp.c:16959
#define FALSE
Definition: def.h:72
methods for the aggregation rows
#define DEFAULT_SLACKSCORE
SCIP_Real SCIPinfinity(SCIP *scip)
int SCIPsnprintf(char *t, int len, const char *s,...)
Definition: misc.c:10253
#define TRUE
Definition: def.h:71
#define SCIPdebug(x)
Definition: pub_message.h:74
const char * SCIPsepaGetName(SCIP_SEPA *sepa)
Definition: sepa.c:689
enum SCIP_Retcode SCIP_RETCODE
Definition: type_retcode.h:53
SCIP_RETCODE SCIPcutGenerationHeuristicCMIR(SCIP *scip, SCIP_SOL *sol, SCIP_Bool postprocess, SCIP_Real boundswitch, SCIP_Bool usevbds, SCIP_Bool allowlocal, int maxtestdelta, int *boundsfortrans, SCIP_BOUNDTYPE *boundtypesfortrans, SCIP_Real minfrac, SCIP_Real maxfrac, SCIP_AGGRROW *aggrrow, SCIP_Real *cutcoefs, SCIP_Real *cutrhs, int *cutinds, int *cutnnz, SCIP_Real *cutefficacy, int *cutrank, SCIP_Bool *cutislocal, SCIP_Bool *success)
Definition: cuts.c:4222
SCIP_RETCODE SCIPincludeSepaAggregation(SCIP *scip)
SCIP_Real * bounddist
int SCIPvarGetProbindex(SCIP_VAR *var)
Definition: var.c:17037
SCIP_ROW ** aggrrows
public methods for problem variables
static SCIP_Real negate(SCIP_Real x)
void SCIPswapReals(SCIP_Real *value1, SCIP_Real *value2)
Definition: misc.c:9868
int SCIPaggrRowGetNNz(SCIP_AGGRROW *aggrrow)
Definition: cuts.c:2360
#define SCIPfreeBlockMemory(scip, ptr)
Definition: scip_mem.h:114
SCIP_VAR ** SCIPvarGetVlbVars(SCIP_VAR *var)
Definition: var.c:17548
void SCIPsortDownRealInt(SCIP_Real *realarray, int *intarray, int len)
SCIP_Real SCIPfeasFrac(SCIP *scip, SCIP_Real val)
SCIP_Bool SCIPisEQ(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
#define SCIPfreeBufferArray(scip, ptr)
Definition: scip_mem.h:142
#define SCIPallocBlockMemory(scip, ptr)
Definition: scip_mem.h:97
int SCIPgetNLPBranchCands(SCIP *scip)
Definition: scip_branch.c:417
public methods for SCIP variables
SCIP_RETCODE SCIPsetSepaCopy(SCIP *scip, SCIP_SEPA *sepa, SCIP_DECL_SEPACOPY((*sepacopy)))
Definition: scip_sepa.c:220
SCIP_Real SCIProwGetDualsol(SCIP_ROW *row)
Definition: lp.c:16979
flow cover and complemented mixed integer rounding cuts separator (Marchand&#39;s version) ...
#define SCIPdebugMsg
Definition: scip_message.h:88
SCIP_RETCODE SCIPaddIntParam(SCIP *scip, const char *name, const char *desc, int *valueptr, SCIP_Bool isadvanced, int defaultvalue, int minvalue, int maxvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip_param.c:155
public methods for separator plugins
int SCIPgetNContVars(SCIP *scip)
Definition: scip_prob.c:2224
SCIP_Real SCIPgetObjNorm(SCIP *scip)
Definition: scip_prob.c:1697
SCIP_Real SCIPepsilon(SCIP *scip)
SCIP_RETCODE SCIPgetVarClosestVlb(SCIP *scip, SCIP_VAR *var, SCIP_SOL *sol, SCIP_Real *closestvlb, int *closestvlbidx)
Definition: scip_var.c:6519
SCIP_Real SCIPgetRowMaxCoef(SCIP *scip, SCIP_ROW *row)
Definition: scip_lp.c:1828
public methods for numerical tolerances
SCIP_SEPADATA * SCIPsepaGetData(SCIP_SEPA *sepa)
Definition: sepa.c:600
SCIP_Bool SCIPaggrRowHasRowBeenAdded(SCIP_AGGRROW *aggrrow, SCIP_ROW *row)
Definition: cuts.c:2327
public methods for querying solving statistics
public methods for the branch-and-bound tree
SCIP_Real SCIPvarGetUbGlobal(SCIP_VAR *var)
Definition: var.c:17354
int SCIPsepaGetFreq(SCIP_SEPA *sepa)
Definition: sepa.c:733
#define DEFAULT_MAXROWFAC
SCIP_Bool SCIPisCutEfficacious(SCIP *scip, SCIP_SOL *sol, SCIP_ROW *cut)
Definition: scip_cut.c:161
#define SEPA_FREQ
static SCIP_Real aggrdataGetBoundDist(AGGREGATIONDATA *aggrdata, int probvaridx)
static SCIP_RETCODE separateCuts(SCIP *scip, SCIP_SEPA *sepa, SCIP_SOL *sol, SCIP_Bool allowlocal, SCIP_RESULT *result)
SCIP_Real SCIPgetRowMinCoef(SCIP *scip, SCIP_ROW *row)
Definition: scip_lp.c:1810
#define MINFRAC
int * SCIPaggrRowGetRowInds(SCIP_AGGRROW *aggrrow)
Definition: cuts.c:2305
static SCIP_RETCODE aggregation(SCIP *scip, AGGREGATIONDATA *aggrdata, SCIP_SEPA *sepa, SCIP_SOL *sol, SCIP_Bool allowlocal, SCIP_Real *rowlhsscores, SCIP_Real *rowrhsscores, int startrow, int maxaggrs, SCIP_Bool *wastried, SCIP_Bool *cutoff, int *cutinds, SCIP_Real *cutcoefs, SCIP_Bool negate, int *ncuts)
SCIP_ROW ** SCIPcolGetRows(SCIP_COL *col)
Definition: lp.c:16828
SCIP_RETCODE SCIPgetSolVals(SCIP *scip, SCIP_SOL *sol, int nvars, SCIP_VAR **vars, SCIP_Real *vals)
Definition: scip_sol.c:1447
#define DEFAULT_MAXAGGRSROOT
SCIP_Bool SCIProwIsLocal(SCIP_ROW *row)
Definition: lp.c:17068
#define SCIPfreeBufferArrayNull(scip, ptr)
Definition: scip_mem.h:143
int SCIPsepaGetNCallsAtNode(SCIP_SEPA *sepa)
Definition: sepa.c:816
SCIP_Bool SCIPisEfficacious(SCIP *scip, SCIP_Real efficacy)
Definition: scip_cut.c:179
#define DEFAULT_MAXROWDENSITY
#define DEFAULT_MAXFAILS
#define MAXFRAC
void SCIPsepaSetData(SCIP_SEPA *sepa, SCIP_SEPADATA *sepadata)
Definition: sepa.c:610
int * SCIPaggrRowGetInds(SCIP_AGGRROW *aggrrow)
Definition: cuts.c:2350
#define REALABS(x)
Definition: def.h:181
static SCIP_DECL_SEPAEXECLP(sepaExeclpAggregation)
void SCIPaggrRowRemoveZeros(SCIP *scip, SCIP_AGGRROW *aggrrow, SCIP_Bool *valid)
Definition: cuts.c:2282
#define SCIP_CALL(x)
Definition: def.h:358
SCIP_RETCODE SCIPgetVarClosestVub(SCIP *scip, SCIP_VAR *var, SCIP_SOL *sol, SCIP_Real *closestvub, int *closestvubidx)
Definition: scip_var.c:6542
SCIP_Real SCIProwGetRhs(SCIP_ROW *row)
Definition: lp.c:16969
SCIP_Real * SCIPvarGetVubCoefs(SCIP_VAR *var)
Definition: var.c:17600
SCIP_RETCODE SCIPaddRow(SCIP *scip, SCIP_ROW *row, SCIP_Bool forcecut, SCIP_Bool *infeasible)
Definition: scip_cut.c:294
SCIP_Bool SCIProwIsModifiable(SCIP_ROW *row)
Definition: lp.c:17078
SCIP_Bool SCIPsortedvecFindInt(int *intarray, int val, int len, int *pos)
SCIP_COL ** SCIProwGetCols(SCIP_ROW *row)
Definition: lp.c:16905
SCIP_RETCODE SCIPincludeSepaBasic(SCIP *scip, SCIP_SEPA **sepa, const char *name, const char *desc, int priority, int freq, SCIP_Real maxbounddist, SCIP_Bool usessubscip, SCIP_Bool delay, SCIP_DECL_SEPAEXECLP((*sepaexeclp)), SCIP_DECL_SEPAEXECSOL((*sepaexecsol)), SCIP_SEPADATA *sepadata)
Definition: scip_sepa.c:178
#define SCIPallocBufferArray(scip, ptr, num)
Definition: scip_mem.h:130
SCIP_Real * SCIProwGetVals(SCIP_ROW *row)
Definition: lp.c:16915
public data structures and miscellaneous methods
#define SEPA_USESSUBSCIP
#define SCIP_Bool
Definition: def.h:69
SCIP_LPSOLSTAT SCIPgetLPSolstat(SCIP *scip)
Definition: scip_lp.c:226
int SCIPgetNImplVars(SCIP *scip)
Definition: scip_prob.c:2179
static SCIP_RETCODE aggregateNextRow(SCIP *scip, SCIP_SEPADATA *sepadata, SCIP_Real *rowlhsscores, SCIP_Real *rowrhsscores, AGGREGATIONDATA *aggrdata, SCIP_AGGRROW *aggrrow, int *naggrs, SCIP_Bool *success)
static SCIP_Bool getRowAggregationCandidates(AGGREGATIONDATA *aggrdata, int probvaridx, SCIP_ROW ***rows, SCIP_Real **rowvarcoefs, int *nrows, int *ngoodrows)
SCIP_Bool SCIPvarIsInLP(SCIP_VAR *var)
Definition: var.c:17069
SCIP_RETCODE SCIPcalcFlowCover(SCIP *scip, SCIP_SOL *sol, SCIP_Bool postprocess, SCIP_Real boundswitch, SCIP_Bool allowlocal, SCIP_AGGRROW *aggrrow, SCIP_Real *cutcoefs, SCIP_Real *cutrhs, int *cutinds, int *cutnnz, SCIP_Real *cutefficacy, int *cutrank, SCIP_Bool *cutislocal, SCIP_Bool *success)
Definition: cuts.c:7409
int SCIPgetDepth(SCIP *scip)
Definition: scip_tree.c:715
int SCIPgetRowNumIntCols(SCIP *scip, SCIP_ROW *row)
Definition: scip_lp.c:1792
#define DEFAULT_MAXTRIES
SCIP_RETCODE SCIPaddPoolCut(SCIP *scip, SCIP_ROW *row)
Definition: scip_cut.c:405
#define MIN(x, y)
Definition: def.h:216
public methods for LP management
SCIP_RETCODE SCIPcreateEmptyRowSepa(SCIP *scip, SCIP_ROW **row, SCIP_SEPA *sepa, const char *name, SCIP_Real lhs, SCIP_Real rhs, SCIP_Bool local, SCIP_Bool modifiable, SCIP_Bool removable)
Definition: scip_lp.c:1365
public methods for cuts and aggregation rows
#define SEPA_NAME
SCIP_AGGRROW * aggrrow
SCIP_COL * SCIPvarGetCol(SCIP_VAR *var)
Definition: var.c:17058
static void destroyAggregationData(SCIP *scip, AGGREGATIONDATA *aggrdata)
static SCIP_RETCODE setupAggregationData(SCIP *scip, SCIP_SOL *sol, SCIP_Bool allowlocal, AGGREGATIONDATA *aggrdata)
SCIP_Bool SCIPisInfinity(SCIP *scip, SCIP_Real val)
SCIP_Real SCIPgetRowSolActivity(SCIP *scip, SCIP_ROW *row, SCIP_SOL *sol)
Definition: scip_lp.c:2050
#define DEFAULT_TRYNEGSCALING
SCIP_Bool SCIPisCutNew(SCIP *scip, SCIP_ROW *row)
Definition: scip_cut.c:387
int SCIPgetNBinVars(SCIP *scip)
Definition: scip_prob.c:2089
public methods for the LP relaxation, rows and columns
int SCIProwGetRank(SCIP_ROW *row)
Definition: lp.c:17048
int SCIPgetNVars(SCIP *scip)
Definition: scip_prob.c:2044
#define SEPA_PRIORITY
#define SCIP_REAL_MAX
Definition: def.h:158
#define DEFAULT_MAXSEPACUTS
#define DEFAULT_MAXAGGDENSITY
SCIP_Real SCIProwGetParallelism(SCIP_ROW *row1, SCIP_ROW *row2, char orthofunc)
Definition: lp.c:7631
SCIP_Real * r
Definition: circlepacking.c:50
methods for sorting joint arrays of various types
public methods for branching rule plugins and branching
#define DEFAULT_MAXROUNDS
SCIP_RETCODE SCIPreleaseRow(SCIP *scip, SCIP_ROW **row)
Definition: scip_lp.c:1474
general public methods
#define MAX(x, y)
Definition: def.h:215
SCIP_RETCODE SCIPsetSepaFree(SCIP *scip, SCIP_SEPA *sepa, SCIP_DECL_SEPAFREE((*sepafree)))
Definition: scip_sepa.c:236
SCIP_Bool SCIPisGT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
#define SEPA_DELAY
#define DEFAULT_DENSITYOFFSET
SCIP_VAR * SCIPcolGetVar(SCIP_COL *col)
Definition: lp.c:16729
public methods for solutions
void SCIProwChgRank(SCIP_ROW *row, int rank)
Definition: lp.c:17181
static SCIP_DECL_SEPAFREE(sepaFreeAggregation)
public methods for message output
SCIP_VAR ** SCIPgetVars(SCIP *scip)
Definition: scip_prob.c:1999
int SCIProwGetLPPos(SCIP_ROW *row)
Definition: lp.c:17148
#define SCIP_Real
Definition: def.h:157
SCIP_Bool SCIPisStopped(SCIP *scip)
Definition: scip_general.c:738
public methods for message handling
SCIP_RETCODE SCIPaggrRowCreate(SCIP *scip, SCIP_AGGRROW **aggrrow)
Definition: cuts.c:1549
SCIP_RETCODE SCIPprintRow(SCIP *scip, SCIP_ROW *row, FILE *file)
Definition: scip_lp.c:2099
SCIP_VAR ** SCIPvarGetVubVars(SCIP_VAR *var)
Definition: var.c:17590
#define DEFAULT_DYNAMICCUTS
#define POSTPROCESS
static SCIP_Real getRowFracActivity(SCIP_ROW *row, SCIP_Real *fractionalities)
SCIP_Bool SCIPisZero(SCIP *scip, SCIP_Real val)
SCIP_Bool SCIPisLE(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
static INLINE SCIP_Real SCIPaggrRowGetProbvarValue(SCIP_AGGRROW *aggrrow, int probindex)
Definition: cuts.h:239
int SCIPgetNLPCols(SCIP *scip)
Definition: scip_lp.c:551
SCIP_Real SCIPvarGetUbLocal(SCIP_VAR *var)
Definition: var.c:17410
SCIP_Real SCIPsumepsilon(SCIP *scip)
public methods for separators
#define BMSclearMemoryArray(ptr, num)
Definition: memory.h:119
SCIP_RETCODE SCIPgetLPRowsData(SCIP *scip, SCIP_ROW ***rows, int *nrows)
Definition: scip_lp.c:573
#define DEFAULT_MAXTRIESROOT
void SCIPaggrRowClear(SCIP_AGGRROW *aggrrow)
Definition: cuts.c:1949
#define DEFAULT_MAXSEPACUTSROOT
SCIP_Longint SCIPgetNLPs(SCIP *scip)
#define SCIPABORT()
Definition: def.h:330
public methods for global and local (sub)problems
int SCIPcolGetNLPNonz(SCIP_COL *col)
Definition: lp.c:16817
#define USEVBDS
SCIP_RETCODE SCIPmakeRowIntegral(SCIP *scip, SCIP_ROW *row, SCIP_Real mindelta, SCIP_Real maxdelta, SCIP_Longint maxdnom, SCIP_Real maxscale, SCIP_Bool usecontvars, SCIP_Bool *success)
Definition: scip_lp.c:1750
SCIP_Real SCIPgetSolVal(SCIP *scip, SCIP_SOL *sol, SCIP_VAR *var)
Definition: scip_sol.c:1410
#define DEFAULT_AGGRTOL
SCIP_Real SCIProwGetNorm(SCIP_ROW *row)
Definition: lp.c:16935
SCIP_RETCODE SCIPaddRealParam(SCIP *scip, const char *name, const char *desc, SCIP_Real *valueptr, SCIP_Bool isadvanced, SCIP_Real defaultvalue, SCIP_Real minvalue, SCIP_Real maxvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip_param.c:211
#define DEFAULT_MAXSLACK
#define SEPA_DESC
struct SCIP_SepaData SCIP_SEPADATA
Definition: type_sepa.h:38
SCIP_RETCODE SCIPaddBoolParam(SCIP *scip, const char *name, const char *desc, SCIP_Bool *valueptr, SCIP_Bool isadvanced, SCIP_Bool defaultvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip_param.c:129
int SCIPgetNSepaRounds(SCIP *scip)
SCIP_Real * aggrrowscoef
struct AggregationData AGGREGATIONDATA
#define SCIPreallocBufferArray(scip, ptr, num)
Definition: scip_mem.h:134
memory allocation routines