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