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