Scippy

SCIP

Solving Constraint Integer Programs

sepa_cmir.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-2014 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_cmir.c
17  * @brief complemented mixed integer rounding cuts separator (Marchand's version)
18  * @author Kati Wolter
19  * @author Tobias Achterberg
20  */
21 
22 /*---+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8----+----9----+----0----+----1----+----2*/
23 
24 #include <assert.h>
25 #include <string.h>
26 
27 #include "scip/sepa_cmir.h"
28 #include "scip/pub_misc.h"
29 
30 
31 #define SEPA_NAME "cmir"
32 #define SEPA_DESC "complemented mixed integer rounding cuts separator (Marchand's version)"
33 #define SEPA_PRIORITY -3000
34 #define SEPA_FREQ 0
35 #define SEPA_MAXBOUNDDIST 0.0
36 #define SEPA_USESSUBSCIP FALSE /**< does the separator use a secondary SCIP instance? */
37 #define SEPA_DELAY FALSE /**< should separation method be delayed, if other separators found cuts? */
38 
39 #define DEFAULT_MAXROUNDS 3 /**< maximal number of cmir separation rounds per node (-1: unlimited) */
40 #define DEFAULT_MAXROUNDSROOT 10 /**< maximal number of cmir separation rounds in the root node (-1: unlimited) */
41 #define DEFAULT_MAXTRIES 100 /**< maximal number of rows to start aggregation with per separation round
42  * (-1: unlimited) */
43 #define DEFAULT_MAXTRIESROOT -1 /**< maximal number of rows to start aggregation with per round in the root node
44  * (-1: unlimited) */
45 #define DEFAULT_MAXFAILS 20 /**< maximal number of consecutive unsuccessful aggregation tries (-1: unlimited) */
46 #define DEFAULT_MAXFAILSROOT 100 /**< maximal number of consecutive unsuccessful aggregation tries in the root node
47  * (-1: unlimited) */
48 #define DEFAULT_MAXAGGRS 3 /**< maximal number of aggregations for each row per separation round */
49 #define DEFAULT_MAXAGGRSROOT 6 /**< maximal number of aggregations for each row per round in the root node */
50 #define DEFAULT_MAXSEPACUTS 100 /**< maximal number of cmir cuts separated per separation round */
51 #define DEFAULT_MAXSEPACUTSROOT 500 /**< maximal number of cmir cuts separated per separation round in root node */
52 #define DEFAULT_MAXSLACK 0.0 /**< maximal slack of rows to be used in aggregation */
53 #define DEFAULT_MAXSLACKROOT 0.1 /**< maximal slack of rows to be used in aggregation in the root node */
54 #define DEFAULT_DENSITYSCORE 1e-04 /**< weight of row density in the aggregation scoring of the rows */
55 #define DEFAULT_SLACKSCORE 1e-03 /**< weight of slack in the aggregation scoring of the rows */
56 #define DEFAULT_MAXAGGDENSITY 0.20 /**< maximal density of aggregated row */
57 #define DEFAULT_MAXROWDENSITY 0.05 /**< maximal density of row to be used in aggregation */
58 #define DEFAULT_DENSITYOFFSET 100 /**< additional number of variables allowed in row on top of density */
59 #define DEFAULT_MAXROWFAC 1e+4 /**< maximal row aggregation factor */
60 #define DEFAULT_MAXTESTDELTA -1 /**< maximal number of different deltas to try (-1: unlimited) */
61 #define DEFAULT_MAXCONTS 10 /**< maximal number of active continuous variables in aggregated row */
62 #define DEFAULT_MAXCONTSROOT 10 /**< maximal number of active continuous variables in aggregated row in the root */
63 #define DEFAULT_AGGRTOL 0.1 /**< aggregation heuristic: tolerance for bound distances used to select real
64  * variable in current aggregated constraint to be eliminated */
65 #define DEFAULT_TRYNEGSCALING TRUE /**< should negative values also be tested in scaling? */
66 #define DEFAULT_FIXINTEGRALRHS TRUE /**< should an additional variable be complemented if f0 = 0? */
67 #define DEFAULT_DYNAMICCUTS TRUE /**< should generated cuts be removed from the LP if they are no longer tight? */
68 
69 #define BOUNDSWITCH 0.5
70 #define USEVBDS TRUE
71 #define ALLOWLOCAL TRUE
72 #define MINFRAC 0.05
73 #define MAXFRAC 0.999
74 #define MAKECONTINTEGRAL FALSE
75 #define IMPLINTSARECONT
76 
77 #define MAXAGGRLEN(nvars) (0.1*(nvars)+1000) /**< maximal length of base inequality */
78 
79 
80 /*
81  * Data structures
82  */
83 
84 /** separator data */
85 struct SCIP_SepaData
86 {
87  SCIP_Real maxslack; /**< maximal slack of rows to be used in aggregation */
88  SCIP_Real maxslackroot; /**< maximal slack of rows to be used in aggregation in the root node */
89  SCIP_Real densityscore; /**< weight of row density in the aggregation scoring of the rows */
90  SCIP_Real slackscore; /**< weight of slack in the aggregation scoring of the rows */
91  SCIP_Real maxaggdensity; /**< maximal density of aggregated row */
92  SCIP_Real maxrowdensity; /**< maximal density of row to be used in aggregation */
93  SCIP_Real maxrowfac; /**< maximal row aggregation factor */
94  SCIP_Real aggrtol; /**< tolerance for bound distance used in aggregation heuristic */
95  int maxrounds; /**< maximal number of cmir separation rounds per node (-1: unlimited) */
96  int maxroundsroot; /**< maximal number of cmir separation rounds in the root node (-1: unlimited) */
97  int maxtries; /**< maximal number of rows to start aggregation with per separation round
98  * (-1: unlimited) */
99  int maxtriesroot; /**< maximal number of rows to start aggregation with per round in the root node
100  * (-1: unlimited) */
101  int maxfails; /**< maximal number of consecutive unsuccessful aggregation tries
102  * (-1: unlimited) */
103  int maxfailsroot; /**< maximal number of consecutive unsuccessful aggregation tries in the root
104  * node (-1: unlimited) */
105  int maxaggrs; /**< maximal number of aggregations for each row per separation round */
106  int maxaggrsroot; /**< maximal number of aggregations for each row per round in the root node */
107  int maxsepacuts; /**< maximal number of cmir cuts separated per separation round */
108  int maxsepacutsroot; /**< maximal number of cmir cuts separated per separation round in root node */
109  int densityoffset; /**< additional number of variables allowed in row on top of density */
110  int maxtestdelta; /**< maximal number of different deltas to try (-1: unlimited) */
111  int maxconts; /**< maximal number of active continuous variables in aggregated row */
112  int maxcontsroot; /**< maximal number of active continuous variables in aggregated row in the root */
113  SCIP_Bool trynegscaling; /**< should negative values also be tested in scaling? */
114  SCIP_Bool fixintegralrhs; /**< should an additional variable be complemented if f0 = 0? */
115  SCIP_Bool dynamiccuts; /**< should generated cuts be removed from the LP if they are no longer tight? */
116 };
117 
118 
119 /*
120  * Local methods
121  */
122 
123 /** stores nonzero elements of dense coefficient vector as sparse vector, and calculates activity and norm */
124 static
126  SCIP* scip, /**< SCIP data structure */
127  int nvars, /**< number of problem variables */
128  SCIP_VAR** vars, /**< problem variables */
129  SCIP_Real* cutcoefs, /**< dense coefficient vector */
130  SCIP_Real* varsolvals, /**< dense variable LP solution vector */
131  SCIP_VAR** cutvars, /**< array to store variables of sparse cut vector */
132  SCIP_Real* cutvals, /**< array to store coefficients of sparse cut vector */
133  int* cutlen, /**< pointer to store number of nonzero entries in cut */
134  SCIP_Real* cutact /**< pointer to store activity of cut */
135  )
136 {
137  SCIP_Real act;
138  int len;
139  int v;
140 
141  assert(nvars == 0 || cutcoefs != NULL);
142  assert(nvars == 0 || varsolvals != NULL);
143  assert(cutvars != NULL);
144  assert(cutvals != NULL);
145  assert(cutlen != NULL);
146  assert(cutact != NULL);
147 
148  len = 0;
149  act = 0.0;
150  for( v = 0; v < nvars; ++v )
151  {
152  SCIP_Real val;
153 
154  val = cutcoefs[v];
155  if( !SCIPisZero(scip, val) )
156  {
157  act += val * varsolvals[v];
158  cutvars[len] = vars[v];
159  cutvals[len] = val;
160  len++;
161  }
162  }
163 
164  *cutlen = len;
165  *cutact = act;
166 
167  return SCIP_OKAY;
168 }
169 
170 /** adds given cut to LP if violated */
171 static
173  SCIP* scip, /**< SCIP data structure */
174  SCIP_SEPA* sepa, /**< separator */
175  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
176  SCIP_Real* varsolvals, /**< solution values of active variables */
177  SCIP_Real* cutcoefs, /**< coefficients of active variables in cut */
178  SCIP_Real cutrhs, /**< right hand side of cut */
179  SCIP_Bool cutislocal, /**< is the cut only locally valid? */
180  SCIP_Bool cutremovable, /**< should the cut be removed from the LP due to aging or cleanup? */
181  int cutrank, /**< rank of the cut */
182  const char* cutclassname, /**< name of cut class to use for row names */
183  SCIP_Bool* cutoff, /**< whether a cutoff has been detected */
184  int* ncuts /**< pointer to count the number of added cuts */
185  )
186 {
187  SCIP_VAR** vars;
188  SCIP_VAR** cutvars;
189  SCIP_Real* cutvals;
190  SCIP_Real cutact;
191  int nvars;
192  int cutlen;
193 
194  assert(scip != NULL);
195  assert(varsolvals != NULL);
196  assert(cutcoefs != NULL);
197  assert(cutoff != NULL);
198  assert(ncuts != NULL);
199 
200  *cutoff = FALSE;
201 
202  /* get active problem variables */
203  SCIP_CALL( SCIPgetVarsData(scip, &vars, &nvars, NULL, NULL, NULL, NULL) );
204  assert(nvars == 0 || vars != NULL);
205 
206  /* get temporary memory for storing the cut as sparse row */
207  SCIP_CALL( SCIPallocBufferArray(scip, &cutvars, nvars) );
208  SCIP_CALL( SCIPallocBufferArray(scip, &cutvals, nvars) );
209 
210  /* store the cut as sparse row, calculate activity and norm of cut */
211  SCIP_CALL( storeCutInArrays(scip, nvars, vars, cutcoefs, varsolvals,
212  cutvars, cutvals, &cutlen, &cutact) );
213 
214  if( cutlen > 0 )
215  {
216  SCIP_Real cutnorm;
217 
218  cutnorm = SCIPgetVectorEfficacyNorm(scip, cutvals, cutlen);
219  if( SCIPisPositive(scip, cutnorm) && SCIPisEfficacious(scip, (cutact - cutrhs)/cutnorm) )
220  {
221  SCIP_ROW* cut;
222  char cutname[SCIP_MAXSTRLEN];
223  SCIP_Bool success;
224 
225  /* create the cut */
226  (void) SCIPsnprintf(cutname, SCIP_MAXSTRLEN, "%s%d_%d", cutclassname, SCIPgetNLPs(scip), *ncuts);
227  SCIP_CALL( SCIPcreateEmptyRowSepa(scip, &cut, sepa, cutname, -SCIPinfinity(scip), cutrhs,
228  cutislocal, FALSE, cutremovable) );
229  SCIP_CALL( SCIPaddVarsToRow(scip, cut, cutlen, cutvars, cutvals) );
230 
231  /* set cut rank */
232  SCIProwChgRank(cut, cutrank);
233 
234  SCIPdebugMessage(" -> found potential %s cut <%s>: activity=%f, rhs=%f, norm=%f, eff=%f\n",
235  cutclassname, cutname, cutact, cutrhs, cutnorm, SCIPgetCutEfficacy(scip, sol, cut));
236  SCIPdebug( SCIP_CALL( SCIPprintRow(scip, cut, NULL) ) );
237 
238  /* try to scale the cut to integral values, but only if the scaling is small; otherwise keep the fractional cut */
239  SCIP_CALL( SCIPmakeRowIntegral(scip, cut, -SCIPepsilon(scip), SCIPsumepsilon(scip),
240  (SCIP_Longint) 30, 100.0, MAKECONTINTEGRAL, &success) );
241  if( success && !SCIPisCutEfficacious(scip, sol, cut) )
242  {
243  SCIPdebugMessage(" -> %s cut <%s> no longer efficacious: act=%f, rhs=%f, norm=%f, eff=%f\n",
244  cutclassname, cutname, cutact, cutrhs, cutnorm, SCIPgetCutEfficacy(scip, sol, cut));
245  SCIPdebug( SCIP_CALL( SCIPprintRow(scip, cut, NULL) ) );
246  success = FALSE;
247  }
248  else
249  success = TRUE; /* also use cut if scaling failed */
250 
251  /* if scaling was successful, add the cut */
252  if( success ) /*lint !e774*/ /* Boolean within 'if' always evaluates to True */
253  {
254  SCIPdebugMessage(" -> found %s cut <%s>: act=%f, rhs=%f, norm=%f, eff=%f, rank=%d, min=%f, max=%f (range=%g)\n",
255  cutclassname, cutname, cutact, cutrhs, cutnorm, SCIPgetCutEfficacy(scip, sol, cut), SCIProwGetRank(cut),
256  SCIPgetRowMinCoef(scip, cut), SCIPgetRowMaxCoef(scip, cut),
257  SCIPgetRowMaxCoef(scip, cut)/SCIPgetRowMinCoef(scip, cut));
258  SCIPdebug( SCIP_CALL( SCIPprintRow(scip, cut, NULL) ) );
259  SCIP_CALL( SCIPaddCut(scip, sol, cut, FALSE, cutoff) );
260  if( !(*cutoff) && !cutislocal )
261  {
262  SCIP_CALL( SCIPaddPoolCut(scip, cut) );
263  }
264  (*ncuts)++;
265  }
266 
267  /* release the row */
268  SCIP_CALL( SCIPreleaseRow(scip, &cut) );
269  }
270  }
271 
272  /* free temporary memory */
273  SCIPfreeBufferArray(scip, &cutvals);
274  SCIPfreeBufferArray(scip, &cutvars);
275 
276  return SCIP_OKAY;
277 }
278 
279 /** adds delta to active continuous variables counter */
280 static
282  SCIP* scip, /**< SCIP data structure */
283  SCIP_Real* varsolvals, /**< LP solution value of all variables in LP */
284  SCIP_Real* bestcontlbs, /**< best lower (variable or standard) bounds of continuous variables */
285  SCIP_Real* bestcontubs, /**< best upper (variable or standard) bounds of continuous variables */
286  int nintvars, /**< number of integer variables */
287  SCIP_VAR* var, /**< continuous variable */
288  int delta, /**< delta value of counters */
289  int* nactiveconts /**< pointer to count number of active continuous variables */
290  )
291 {
292  assert(nactiveconts != NULL);
293 
294  if( !SCIPvarIsIntegral(var) )
295  {
296  SCIP_Real primsol;
297  SCIP_Real lb;
298  SCIP_Real ub;
299  int probindex;
300 
301  probindex = SCIPvarGetProbindex(var);
302  assert(probindex >= nintvars);
303 
304  primsol = varsolvals[probindex];
305  lb = bestcontlbs[probindex - nintvars];
306  ub = bestcontubs[probindex - nintvars];
307 
308  if( SCIPisLT(scip, lb, primsol) && SCIPisLT(scip, primsol, ub) )
309  (*nactiveconts) += delta;
310  }
311 }
312 
313 /** decreases the score of a row in order to not aggregate it again too soon */
314 static
316  SCIP* scip, /**< SCIP data structure */
317  SCIP_Real* rowlhsscores, /**< aggregation scores for left hand sides of row */
318  SCIP_Real* rowrhsscores, /**< aggregation scores for right hand sides of row */
319  int rowidx /**< index of row to decrease score for */
320  )
321 {
322  assert(rowlhsscores != NULL);
323  assert(rowrhsscores != NULL);
324  assert(rowlhsscores[rowidx] >= 0.0);
325  assert(rowrhsscores[rowidx] >= 0.0);
326 
327  rowlhsscores[rowidx] *= 0.9;
328  rowrhsscores[rowidx] *= 0.9;
329 }
330 
331 /** calculates the c-MIR cut for the given rowweights and delta value, and updates testeddeltas, bestdelta, and
332  * bestefficacy
333  */
334 static
336  SCIP* scip, /**< SCIP data structure */
337  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
338  int nvars, /**< number of problem variables */
339  SCIP_Real* rowweights, /**< weight of rows in aggregated row */
340  SCIP_Real* cutcoefs, /**< array to store the cut coefficients */
341  SCIP_Real* mksetcoefs, /**< array to store mixed knapsack set coefficients: size nvars; or NULL */
342  SCIP_Bool* mksetcoefsvalid, /**< pointer to store whether mixed knapsack set coefficients are valid; or NULL */
343  SCIP_Real* testeddeltas, /**< array with already tested deltas */
344  int* ntesteddeltas, /**< pointer to the number of elements in testeddeltas */
345  SCIP_Real delta, /**< delta value to scale mixed knapsack equation with */
346  SCIP_Real boundswitch, /**< fraction of domain up to which lower bound is used in transformation */
347  SCIP_Bool usevbds, /**< should variable bounds be used in bound transformation? */
348  SCIP_Bool allowlocal, /**< should local information allowed to be used, resulting in a local cut? */
349  SCIP_Bool fixintegralrhs, /**< should complementation tried to be adjusted such that rhs gets fractional? */
350  int maxmksetcoefs, /**< maximal number of nonzeros allowed in aggregated base inequality */
351  SCIP_Real maxweightrange, /**< maximal valid range max(|weights|)/min(|weights|) of row weights */
352  SCIP_Real minfrac, /**< minimal fractionality of rhs to produce MIR cut for */
353  SCIP_Real maxfrac, /**< maximal fractionality of rhs to produce MIR cut for */
354  SCIP_Real* bestdelta, /**< pointer to the currently best delta value */
355  SCIP_Real* bestefficacy /**< pointer to the currently best efficacy */
356  )
357 {
358  SCIP_Bool tested;
359  int i;
360 
361  assert(testeddeltas != NULL);
362  assert(ntesteddeltas != NULL);
363  assert(bestdelta != NULL);
364  assert(bestefficacy != NULL);
365 
366  /* do not use too small deltas */
367  if( SCIPisFeasZero(scip, delta) )
368  return SCIP_OKAY;
369 
370  /* check, if delta with mult was already tested */
371  tested = FALSE;
372  for( i = 0; i < *ntesteddeltas && !tested; i++ )
373  tested = SCIPisEQ(scip, testeddeltas[i], delta);
374  if( !tested )
375  {
376  SCIP_Real cutact;
377  SCIP_Real cutrhs;
378  SCIP_Bool success;
379  SCIP_Bool cutislocal;
380 
381  testeddeltas[*ntesteddeltas] = delta;
382  (*ntesteddeltas)++;
383 
384  /* create a MIR cut out of the weighted LP rows */
385  SCIP_CALL( SCIPcalcMIR(scip, sol, boundswitch, usevbds, allowlocal, fixintegralrhs, NULL, NULL, maxmksetcoefs,
386  maxweightrange, minfrac, maxfrac, rowweights, NULL, delta, mksetcoefs, mksetcoefsvalid, cutcoefs, &cutrhs, &cutact,
387  &success, &cutislocal, NULL) );
388  assert(allowlocal || !cutislocal);
389  SCIPdebugMessage("delta = %g -> success: %u, cutact: %g, cutrhs: %g, vio: %g\n",
390  delta, success, success ? cutact : 0.0, success ? cutrhs : 0.0, success ? cutact - cutrhs : 0.0);
391 
392  /* check if delta generates cut which is more violated */
393  if( success && SCIPisFeasGT(scip, cutact, cutrhs) )
394  {
395  SCIP_Real norm;
396 
397  norm = SCIPgetVectorEfficacyNorm(scip, cutcoefs, nvars);
398  if( norm > 0.0 )
399  {
400  SCIP_Real efficacy;
401 
402  efficacy = (cutact - cutrhs)/norm;
403  SCIPdebugMessage("act = %g rhs = %g eff = %g, old besteff = %g, old bestdelta=%g\n",
404  cutact, cutrhs, efficacy, *bestefficacy, *bestdelta);
405  if( efficacy > *bestefficacy )
406  {
407  *bestdelta = delta;
408  *bestefficacy = efficacy;
409  }
410  }
411  }
412  }
413 
414  return SCIP_OKAY;
415 }
416 
417 /** Performs the cut generation heuristic of the c-MIR separation algorithm, i.e., tries to generate a c-MIR cut which is
418  * valid for the mixed knapsack set corresponding to the current aggregated constraint. Cuts will only be added here if
419  * no pointer to store best scaling factor delta is given.
420  */
422  SCIP* scip, /**< SCIP data structure */
423  SCIP_SEPA* sepa, /**< separator */
424  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
425  SCIP_Real* varsolvals, /**< LP solution value of all variables in LP */
426  int maxtestdelta, /**< maximal number of different deltas to try (-1: unlimited) */
427  SCIP_Real* rowweights, /**< weight of rows in aggregated row */
428  SCIP_Real boundswitch, /**< fraction of domain up to which lower bound is used in transformation */
429  SCIP_Bool usevbds, /**< should variable bounds be used in bound transformation? */
430  SCIP_Bool allowlocal, /**< should local information allowed to be used, resulting in a local cut? */
431  SCIP_Bool fixintegralrhs, /**< should complementation tried to be adjusted such that rhs gets fractional? */
432  int maxmksetcoefs, /**< maximal number of nonzeros allowed in aggregated base inequality */
433  SCIP_Real maxweightrange, /**< maximal valid range max(|weights|)/min(|weights|) of row weights */
434  SCIP_Real minfrac, /**< minimal fractionality of rhs to produce MIR cut for */
435  SCIP_Real maxfrac, /**< maximal fractionality of rhs to produce MIR cut for */
436  SCIP_Bool trynegscaling, /**< should negative values also be tested in scaling? */
437  SCIP_Bool cutremovable, /**< should the cut be removed from the LP due to aging or cleanup? */
438  const char* cutclassname, /**< name of cut class to use for row names */
439  SCIP_Bool* cutoff, /**< whether a cutoff has been detected */
440  int* ncuts, /**< pointer to count the number of generated cuts */
441  SCIP_Real* delta, /**< pointer to store best delta found; NULL, if cut should be added here */
442  SCIP_Bool* deltavalid /**< pointer to store whether best delta value is valid or NULL */
443 )
444 { /*lint --e{715}*/
445  SCIP_VAR** vars;
446  SCIP_Real* cutcoefs;
447  SCIP_Real* mksetcoefs;
448  SCIP_Real* testeddeltas;
449  SCIP_Real bestdelta;
450  SCIP_Real bestefficacy;
451  SCIP_Real maxabsmksetcoef;
452  SCIP_Bool mksetcoefsvalid;
453  int nvars;
454  int ncontvars;
455  int nintvars;
456  int ntesteddeltas;
457  int vi;
458 
459  assert( cutoff != NULL );
460  *cutoff = FALSE;
461 
462  if( maxtestdelta == -1 )
463  maxtestdelta = INT_MAX;
464 
465  if( delta != NULL )
466  *deltavalid = FALSE;
467 
468  /* get active problem variables */
469  vars = SCIPgetVars(scip);
470  nvars = SCIPgetNVars(scip);
471  ncontvars = SCIPgetNContVars(scip);
472  nintvars = nvars-ncontvars;
473  if( nvars == 0 )
474  return SCIP_OKAY;
475  assert(vars != NULL);
476 
477  /* get temporary memory */
478  SCIP_CALL( SCIPallocBufferArray(scip, &mksetcoefs, nvars) );
479  SCIP_CALL( SCIPallocBufferArray(scip, &cutcoefs, nvars) );
480  SCIP_CALL( SCIPallocBufferArray(scip, &testeddeltas, 3 + 2*(nintvars+2)) );
481 
482  /* As in Marchand's version. Use the absolute value of the coefficients of the integer variables (lying
483  * strictly between its bounds) in the constructed mixed knapsack set, i.e.,
484  * N* = { |alpha'_j| : j in N, alpha'_j != 0 and l_j < x*_j < u_j }
485  */
486 
487  /* search delta for generating a cut with maximum efficacy:
488  * delta = coefficient of integer variable in constructed mixed knapsack set which lies between its bounds
489  */
490  ntesteddeltas = 0;
491  bestdelta = 0.0;
492  bestefficacy = 0.0;
493  maxabsmksetcoef = 0.0;
494  mksetcoefsvalid = FALSE;
495 
496  /* try delta = 1 and get the coefficients of all variables in the constructed mixed knapsack set;
497  * if the aggregated row contains too many nonzero elements the generation of the c-MIR cut is aborted,
498  * in this case, mksetcoefs is not valid and we can abort the separation heuristic (as the number of nonzeros
499  * keeps the same for different values of delta)
500  */
501  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, cutcoefs, mksetcoefs, &mksetcoefsvalid, testeddeltas, &ntesteddeltas,
502  1.0, boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs, maxweightrange, minfrac, maxfrac, &bestdelta,
503  &bestefficacy) );
504  if( mksetcoefsvalid && trynegscaling )
505  {
506  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, cutcoefs, NULL, NULL, testeddeltas, &ntesteddeltas, -1.0,
507  boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs, maxweightrange, minfrac, maxfrac,
508  &bestdelta, &bestefficacy) );
509  }
510 
511  /* find mult in { +1, -1 } and delta in the corresponding set N* leading to the most violated c-MIR cut */
512  for( vi = 0; mksetcoefsvalid && vi < nintvars; vi++ )
513  {
514  SCIP_VAR* var;
515  SCIP_Real primsol;
516  SCIP_Real lb;
517  SCIP_Real ub;
518  SCIP_Real absmksetcoef;
519 
520  var = vars[vi];
521  assert(vi == SCIPvarGetProbindex(var));
522  assert(SCIPvarGetType(var) != SCIP_VARTYPE_CONTINUOUS);
523  assert(SCIPvarIsActive(var));
524  assert(SCIPvarIsIntegral(var));
525 
526  /* update maximum coefficient of integer variables in constructed mixed knapsack set for
527  * mult = +1 and delta = 1 and
528  * mult = -1 and delta = 1
529  */
530  absmksetcoef = REALABS(mksetcoefs[vi]);
531  maxabsmksetcoef = MAX(maxabsmksetcoef, absmksetcoef);
532 
533  if( ntesteddeltas >= maxtestdelta )
534  continue; /* remaining loop is only for maxabsmksetcoef calculation */
535 
536  /* ignore variables with current solution value on its bounds */
537  primsol = varsolvals[vi];
538  lb = SCIPvarGetLbLocal(var);
539  ub = SCIPvarGetUbLocal(var);
540  if( SCIPisEQ(scip, primsol, lb) || SCIPisEQ(scip, primsol, ub) )
541  continue;
542 
543  /* try to divide aggregated row by absmksetcoef */
544  if( !SCIPisFeasZero(scip, absmksetcoef) )
545  {
546  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, cutcoefs, NULL, NULL, testeddeltas, &ntesteddeltas,
547  1.0/absmksetcoef, boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs, maxweightrange, minfrac,
548  maxfrac, &bestdelta, &bestefficacy) );
549  if( trynegscaling )
550  {
551  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, cutcoefs, NULL, NULL, testeddeltas, &ntesteddeltas,
552  -1.0/absmksetcoef, boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs, maxweightrange,
553  minfrac, maxfrac, &bestdelta, &bestefficacy) );
554  }
555  }
556  }
557 
558  /* additionally try delta = maxabscoef+1 */
559  if( mksetcoefsvalid && !SCIPisFeasZero(scip, maxabsmksetcoef) )
560  {
561  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, cutcoefs, NULL, NULL, testeddeltas, &ntesteddeltas,
562  1.0/(maxabsmksetcoef+1.0), boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs, maxweightrange,
563  minfrac, maxfrac, &bestdelta, &bestefficacy) );
564  if( trynegscaling )
565  {
566  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, cutcoefs, NULL, NULL, testeddeltas, &ntesteddeltas,
567  -1.0/(maxabsmksetcoef+1.0), boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs, maxweightrange,
568  minfrac, maxfrac, &bestdelta, &bestefficacy) );
569  }
570  }
571 
572  /* delta found */
573  if( mksetcoefsvalid && SCIPisEfficacious(scip, bestefficacy) )
574  {
575  SCIP_Real currentdelta;
576  SCIP_Real cutrhs;
577  SCIP_Real cutact;
578  SCIP_Bool success;
579  SCIP_Bool cutislocal;
580  int cutrank;
581  int i;
582 
583  assert(!SCIPisFeasZero(scip, bestdelta));
584 
585  /* Try to improve efficacy by multiplying delta with 2, 4 and 8 */
586  for( i = 0, currentdelta = 2.0 * bestdelta; i < 3; i++, currentdelta *= 2.0 )
587  {
588  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, cutcoefs, NULL, NULL, testeddeltas, &ntesteddeltas,
589  currentdelta, boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs, maxweightrange, minfrac,
590  maxfrac, &bestdelta, &bestefficacy) );
591  }
592 
593  /* if no pointer to store delta is given, add cut here (zerohalf cuts will be stored in a separate cut pool first) */
594  if( delta == NULL )
595  {
596  /* generate cut with bestdelta and best boundswitch value */
597  SCIP_CALL( SCIPcalcMIR(scip, sol, boundswitch, usevbds, allowlocal, fixintegralrhs, NULL, NULL,
598  maxmksetcoefs, maxweightrange, minfrac, maxfrac, rowweights, NULL, bestdelta, NULL, NULL, cutcoefs,
599  &cutrhs, &cutact, &success, &cutislocal, &cutrank) );
600  assert(allowlocal || !cutislocal);
601  assert(success);
602 
603  /* add the cut to the separation storage */
604  SCIP_CALL( addCut(scip, sepa, sol, varsolvals, cutcoefs, cutrhs, cutislocal, cutremovable, cutrank, cutclassname, cutoff, ncuts) );
605  }
606  else
607  {
608  *delta = bestdelta;
609  *deltavalid = TRUE;
610  }
611  }
612 
613  /* free datastructures */
614  SCIPfreeBufferArray(scip, &testeddeltas);
615  SCIPfreeBufferArray(scip, &cutcoefs);
616  SCIPfreeBufferArray(scip, &mksetcoefs);
617 
618  return SCIP_OKAY;
619 }
620 
621 /** returns whether the variable should be tried to be aggregated out */
622 static
624  SCIP_VAR* var /**< problem variable */
625  )
626 {
627  SCIP_VARTYPE vartype;
628 
629  vartype = SCIPvarGetType(var);
630 
631 #ifdef IMPLINTSARECONT
632  return (vartype == SCIP_VARTYPE_CONTINUOUS || vartype == SCIP_VARTYPE_IMPLINT);
633 #else
634  return (vartype == SCIP_VARTYPE_CONTINUOUS);
635 #endif
636 }
637 
638 /** returns the minimal distance of the solution of a continuous variable to its bounds */
639 static
641  SCIP* scip, /**< SCIP data structure */
642  int nintvars, /**< number of integer variables in the problem */
643  SCIP_Real* varsolvals, /**< LP solution value of all variables in LP */
644  SCIP_Real* bestcontlbs, /**< best lower (variable or standard) bounds of continuous variables */
645  SCIP_Real* bestcontubs, /**< best upper (variable or standard) bounds of continuous variables */
646  SCIP_VAR* var /**< continuous variable to get bound distance for */
647  )
648 {
649  SCIP_Real primsol;
650  SCIP_Real lb;
651  SCIP_Real ub;
652  SCIP_Real distlower;
653  SCIP_Real distupper;
654  SCIP_Real bounddist;
655 
656  assert(varIsContinuous(var));
657 
658  primsol = varsolvals[SCIPvarGetProbindex(var)];
659  lb = bestcontlbs[SCIPvarGetProbindex(var) - nintvars];
660  ub = bestcontubs[SCIPvarGetProbindex(var) - nintvars];
661  assert(SCIPisGE(scip, lb, SCIPvarGetLbGlobal(var)));
662  assert(SCIPisLE(scip, ub, SCIPvarGetUbGlobal(var)));
663  distlower = primsol - lb;
664  distupper = ub - primsol;
665  bounddist = MIN(distlower, distupper);
666 
667 #ifdef IMPLINTSARECONT
668  /* prefer continuous variables over implicit integers to be aggregated out */
670  bounddist /= 10.0;
671 #endif
672 
673  return bounddist;
674 }
675 
676 /** aggregates different single mixed integer constraints by taking linear combinations of the rows of the LP */
677 static
679  SCIP* scip, /**< SCIP data structure */
680  SCIP_SEPA* sepa, /**< separator */
681  SCIP_SEPADATA* sepadata, /**< separator data */
682  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
683  SCIP_Real* varsolvals, /**< LP solution value of all variables in LP */
684  SCIP_Real* bestcontlbs, /**< best lower (variable or standard) bounds of continuous variables */
685  SCIP_Real* bestcontubs, /**< best upper (variable or standard) bounds of continuous variables */
686  SCIP_Real* contvarscorebounds, /**< bounds on the maximal rowlhsscores and rowrhsscores the variable is contained in */
687  SCIP_Real* rowlhsscores, /**< aggregation scores for left hand sides of row */
688  SCIP_Real* rowrhsscores, /**< aggregation scores for right hand sides of row */
689  int startrow, /**< index of row to start aggregation */
690  int maxaggrs, /**< maximal number of aggregations */
691  SCIP_Real maxslack, /**< maximal slack of rows to be used in aggregation */
692  int maxconts, /**< maximal number of active continuous variables in aggregated row */
693  SCIP_Bool* wastried, /**< pointer to store whether the given startrow was actually tried */
694  SCIP_Bool* cutoff, /**< whether a cutoff has been detected */
695  int* ncuts /**< pointer to count the number of generated cuts */
696  )
697 {
698  SCIP_COL** startnonzcols;
699  SCIP_COL** cols;
700  SCIP_VAR** vars;
701  SCIP_ROW** rows;
702  SCIP_COL* bestcol;
703  SCIP_Real* startnonzcoefs;
704  SCIP_Real* aggrcoefs;
705  SCIP_Real* rowweights;
706  int* aggrcontnonzposs;
707  SCIP_Real* aggrcontnonzbounddists;
708  SCIP_Real maxweight;
709  SCIP_Real minweight;
710  SCIP_Real startrowact;
711  SCIP_Bool hasfractional;
712  int naggrintnonzs;
713  int naggrcontnonzs;
714  int maxaggrnonzs;
715  int nstartnonzcols;
716  int naggrs;
717  int nactiveconts;
718  int nvars;
719  int nintvars;
720  int ncontvars;
721  int ncols;
722  int nrows;
723  int c;
724  int r;
725 
726  assert(scip != NULL);
727  assert(sepadata != NULL);
728  assert(varsolvals != NULL);
729  assert(rowlhsscores != NULL);
730  assert(rowrhsscores != NULL);
731  assert(wastried != NULL);
732  assert(cutoff != NULL);
733  assert(ncuts != NULL);
734 
735  *cutoff = FALSE;
736  *wastried = FALSE;
737 
738  SCIP_CALL( SCIPgetVarsData(scip, &vars, &nvars, NULL, NULL, NULL, &ncontvars) );
739 #ifdef IMPLINTSARECONT
740  ncontvars += SCIPgetNImplVars(scip); /* also aggregate out implicit integers */
741 #endif
742  nintvars = nvars - ncontvars;
743  assert((nvars == 0 && nintvars == 0 && ncontvars == 0) || vars != NULL);
744  SCIP_CALL( SCIPgetLPColsData(scip, &cols, &ncols) );
745  assert(ncols == 0 || cols != NULL);
746  SCIP_CALL( SCIPgetLPRowsData(scip, &rows, &nrows) );
747  assert(nrows == 0 || rows != NULL);
748  assert(0 <= startrow && startrow < nrows);
749 
750  SCIPdebugMessage("start c-MIR aggregation with row <%s> (%d/%d)\n", SCIProwGetName(rows[startrow]), startrow, nrows);
751 
752  /* calculate maximal number of non-zeros in aggregated row */
753  maxaggrnonzs = (int)(sepadata->maxaggdensity * ncols) + sepadata->densityoffset;
754 
755  /* get temporary memory */
756  SCIP_CALL( SCIPallocBufferArray(scip, &aggrcoefs, ncols) );
757  SCIP_CALL( SCIPallocBufferArray(scip, &aggrcontnonzposs, ncols) );
758  SCIP_CALL( SCIPallocBufferArray(scip, &aggrcontnonzbounddists, ncols) );
759  SCIP_CALL( SCIPallocBufferArray(scip, &rowweights, nrows) );
760 
761  /* initialize weights of rows in aggregation */
762  BMSclearMemoryArray(rowweights, nrows);
763  startrowact = SCIPgetRowSolActivity(scip, rows[startrow], sol);
764  if( startrowact <= 0.5 * SCIProwGetLhs(rows[startrow]) + 0.5 * SCIProwGetRhs(rows[startrow]) )
765  rowweights[startrow] = -1.0;
766  else
767  rowweights[startrow] = 1.0;
768  maxweight = 1.0;
769  minweight = 1.0;
770 
771  /* get nonzero columns and coefficients of startrow */
772  startnonzcols = SCIProwGetCols(rows[startrow]);
773  nstartnonzcols = SCIProwGetNLPNonz(rows[startrow]);
774  startnonzcoefs = SCIProwGetVals(rows[startrow]);
775 
776  /* for all columns of startrow store coefficient as coefficient in aggregated row */
777  BMSclearMemoryArray(aggrcoefs, ncols);
778  naggrintnonzs = 0;
779  naggrcontnonzs = 0;
780  nactiveconts = 0;
781  hasfractional = FALSE;
782  for( c = 0; c < nstartnonzcols; c++ )
783  {
784  SCIP_VAR* var;
785  int pos;
786 
787  var = SCIPcolGetVar(startnonzcols[c]);
788  pos = SCIPcolGetLPPos(startnonzcols[c]);
789  assert(pos >= 0);
790  assert(!SCIPisZero(scip, startnonzcoefs[c]));
791  aggrcoefs[pos] = rowweights[startrow] * startnonzcoefs[c];
792  if( varIsContinuous(var) )
793  {
794  SCIP_Real bounddist;
795 
796  updateNActiveConts(scip, varsolvals, bestcontlbs, bestcontubs, nintvars, var, +1, &nactiveconts);
797 
798  /* store continuous variable in array sorted by distance to closest bound */
799  bounddist = getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var);
800  SCIPsortedvecInsertDownRealInt(aggrcontnonzbounddists, aggrcontnonzposs, bounddist, pos, &naggrcontnonzs, NULL);
801  }
802  else
803  naggrintnonzs++;
804 
805  if( !hasfractional && SCIPvarIsIntegral(var) )
806  {
807  SCIP_Real primsol;
808 
809  primsol = varsolvals[SCIPvarGetProbindex(var)];
810  hasfractional = !SCIPisFeasIntegral(scip, primsol);
811  }
812  }
813  assert(naggrintnonzs + naggrcontnonzs == nstartnonzcols);
814 
815  /* don't try aggregation if there is no integer variable with fractional value */
816  if( !hasfractional )
817  {
818  SCIPdebugMessage(" -> row has no fractional integer variables: ignore\n");
819  maxaggrs = -1;
820  }
821 
822  /* decrease score of startrow in order to not aggregate it again too soon */
823  decreaseRowScore(scip, rowlhsscores, rowrhsscores, startrow);
824 
825  /* try to generate cut from the current aggregated row
826  * add cut if found, otherwise add another row to aggregated row
827  * in order to get rid of a continuous variable
828  */
829  naggrs = 0;
830  while( nactiveconts <= maxconts && naggrs <= maxaggrs && naggrcontnonzs + naggrintnonzs <= maxaggrnonzs )
831  {
832  SCIP_ROW* bestrow;
833  SCIP_COL** bestrownonzcols; /* columns with nonzero coefficients in best row to add */
834  SCIP_Real* bestrownonzcoefs; /* nonzero coefficients of columns in best row to add */
835  int nbestrownonzcols; /* number of columns with nonzero coefficients in best row to add */
836  SCIP_Real bestbounddist;
837  SCIP_Real bestscore;
838  int bestrowpos;
839  SCIP_Real aggrfac;
840  SCIP_Real absaggrfac;
841  int nzi;
842  int oldncuts;
843  int ncanceledcontnonzs;
844 
845  *wastried = TRUE;
846 
847 #ifdef SCIP_DEBUG
848  SCIPdebugMessage("aggregation of startrow %d and %d additional rows with %d integer and %d continuous variables (%d active):\n",
849  startrow, naggrs, naggrintnonzs, naggrcontnonzs, nactiveconts);
850  for( c = 0; c < ncols; ++c )
851  {
852  if( aggrcoefs[c] != 0.0 )
853  SCIPdebugPrintf(" %+g<%s>(%g)", aggrcoefs[c], SCIPvarGetName(SCIPcolGetVar(cols[c])),
854  varsolvals[SCIPvarGetProbindex(SCIPcolGetVar(cols[c]))]);
855  }
856  SCIPdebugPrintf("\n");
857 #endif
858 
859  /* Step 1:
860  * try to generate a MIR cut out of the current aggregation
861  */
862  oldncuts = *ncuts;
863  SCIP_CALL( SCIPcutGenerationHeuristicCmir(scip, sepa, sol, varsolvals, sepadata->maxtestdelta, rowweights, BOUNDSWITCH,
864  USEVBDS, ALLOWLOCAL, sepadata->fixintegralrhs, (int) MAXAGGRLEN(nvars), sepadata->maxrowfac, MINFRAC, MAXFRAC,
865  sepadata->trynegscaling, sepadata->dynamiccuts, "cmir", cutoff, ncuts, NULL, NULL) );
866 
867  if ( *cutoff )
868  break;
869 
870  /* if the cut was successfully added, abort the aggregation of further rows */
871  if( *ncuts > oldncuts )
872  {
873  SCIPdebugMessage(" -> abort aggregation: cut found\n");
874  break;
875  }
876 
877  /* Step 2:
878  * aggregate an additional row in order to remove a continuous variable
879  */
880 
881  /* abort, if we reached the maximal number of aggregations */
882  if( naggrs == maxaggrs )
883  {
884  SCIPdebugMessage(" -> abort aggregation: %s\n", nactiveconts == 0 ? "no more active continuous variables"
885  : "maximal number of aggregations reached");
886  break;
887  }
888 
889  SCIPdebugMessage(" -> search column to eliminate\n");
890 
891  /* search for "best" continuous variable in aggregated row:
892  * - solution value is strictly between lower and upper bound
893  * - it exists a not yet aggregated row with nonzero coefficient in this column
894  * out of these variables:
895  * - prefer variables with larger distance of current solution value to its bounds
896  * - of those with large bound distance, prefer variables that can be eliminated with a row of high score
897  */
898  bestcol = NULL;
899  bestbounddist = -1.0;
900  bestscore = 0.0;
901  bestrow = NULL;
902  aggrfac = 0.0;
903  for( nzi = 0; nzi < naggrcontnonzs; ++nzi )
904  {
905  SCIP_COL* col;
906  SCIP_VAR* var;
907  SCIP_Real bounddist;
908 
909  c = aggrcontnonzposs[nzi];
910  assert(0 <= c && c < ncols);
911  assert(!SCIPisZero(scip, aggrcoefs[c]));
912 
913  col = cols[c];
914  var = SCIPcolGetVar(col);
915  assert(varIsContinuous(var));
916  assert(SCIPvarGetProbindex(var) >= nintvars);
917 
918  bounddist = aggrcontnonzbounddists[nzi];
919  assert(SCIPisEQ(scip, bounddist, getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var)));
920  assert(bounddist <= bestbounddist || bestbounddist == -1.0);
921 
922  /* check, if variable is candidate to be the new best variable */
923  if( bounddist >= bestbounddist - sepadata->aggrtol )
924  {
925  SCIP_ROW** nonzrows;
926  SCIP_Real* nonzcoefs;
927  SCIP_Real maxrowscore;
928  int nnonzrows;
929  int probindex;
930 
931  probindex = SCIPvarGetProbindex(var);
932  assert(probindex >= nintvars);
933 
934  SCIPdebugMessage(" -> col <%s>[%g,%g]: sol=%g, dist=%g\n",
935  SCIPvarGetName(var), bestcontlbs[probindex - nintvars],
936  bestcontubs[probindex - nintvars], varsolvals[probindex], bounddist);
937 
938  /* if we know that we will not find a better row, just skip the column */
939  if( contvarscorebounds[probindex - nintvars] <= bestscore )
940  continue;
941 
942  /* look for "best" row to add (minimal slack), but don't add rows again,
943  * that are already involved in aggregation
944  */
945  nnonzrows = SCIPcolGetNLPNonz(col);
946  nonzrows = SCIPcolGetRows(col);
947  nonzcoefs = SCIPcolGetVals(col);
948  maxrowscore = 0.0;
949 
950  for( r = 0; r < nnonzrows; r++ )
951  {
952  SCIP_Real score;
953  SCIP_Real rowscore;
954  SCIP_Real factor;
955  SCIP_Real absfactor;
956  SCIP_Real activity;
957  SCIP_Real lhs;
958  SCIP_Real rhs;
959  int lppos;
960 
961  lppos = SCIProwGetLPPos(nonzrows[r]);
962  assert(0 <= lppos && lppos < nrows);
963 
964  SCIPdebugMessage(" -> r=%d row <%s>: weight=%g, pos=%d, alpha_j=%g, a^r_j=%g, factor=%g, %g <= %g <= %g\n",
965  r, SCIProwGetName(nonzrows[r]), rowweights[lppos], lppos, aggrcoefs[c], nonzcoefs[r],
966  - aggrcoefs[c] / nonzcoefs[r], SCIProwGetLhs(nonzrows[r]),
967  SCIPgetRowSolActivity(scip, nonzrows[r], sol), SCIProwGetRhs(nonzrows[r]));
968 
969  /* update maxrowscore */
970  rowscore = MAX(rowlhsscores[lppos], rowrhsscores[lppos]);
971  maxrowscore = MAX(maxrowscore, rowscore);
972 
973  /* if even the better rowscore does not improve the bestscore, ignore the row */
974  if( rowscore <= bestscore )
975  continue;
976 
977  /* take only unmodifiable LP rows, that are not yet aggregated */
978  if( rowweights[lppos] != 0.0 || SCIProwIsModifiable(nonzrows[r]) )
979  continue;
980 
981  /* don't aggregate rows that would lead to a too extreme aggregation factor */
982  factor = - aggrcoefs[c] / nonzcoefs[r];
983  absfactor = REALABS(factor);
984  if( !SCIPisPositive(scip, absfactor)
985  || absfactor > sepadata->maxrowfac * minweight
986  || maxweight > sepadata->maxrowfac * absfactor )
987  continue;
988 
989  /* for selected real variable y_k, select constraint r with best score SCORE_r with r in P\Q,
990  * where P\Q is the set of constraints not yet involved in the aggregation set
991  */
992  assert(!SCIPisInfinity(scip, -SCIProwGetLhs(nonzrows[r])) || rowlhsscores[lppos] == 0.0);
993  assert(!SCIPisInfinity(scip, SCIProwGetRhs(nonzrows[r])) || rowrhsscores[lppos] == 0.0);
994  score = (factor < 0.0 ? rowlhsscores[lppos] : rowrhsscores[lppos]);
995  if( score <= bestscore )
996  continue;
997 
998  /* check, if the row's slack multiplied with the aggregation factor is too large */
999  activity = SCIPgetRowSolActivity(scip, nonzrows[r], sol);
1000  lhs = SCIProwGetLhs(nonzrows[r]);
1001  rhs = SCIProwGetRhs(nonzrows[r]);
1002  if( (factor < 0.0 && SCIPisGT(scip, factor * (lhs - activity), maxslack))
1003  || (factor > 0.0 && SCIPisGT(scip, factor * (rhs - activity), maxslack)) )
1004  continue;
1005 
1006  /* the row passed all tests: it is the best candidate up to now */
1007  bestbounddist = bounddist;
1008  bestscore = score;
1009  bestcol = col;
1010  bestrow = nonzrows[r];
1011  aggrfac = factor;
1012  SCIPdebugMessage(" -> col <%s>: %g * row <%s>, bounddist=%g, score=%g\n",
1013  SCIPvarGetName(SCIPcolGetVar(bestcol)), aggrfac, SCIProwGetName(bestrow), bestbounddist, score);
1014  }
1015 
1016  /* update score bound of column */
1017  assert(maxrowscore <= contvarscorebounds[probindex - nintvars]);
1018  contvarscorebounds[probindex - nintvars] = maxrowscore;
1019  }
1020  else
1021  {
1022  /* since the nonzero continuous variables are sorted by bound distance, we can abort now */
1023  break;
1024  }
1025  }
1026  assert((bestcol == NULL) == (bestrow == NULL));
1027 
1028 #ifndef NDEBUG
1029  /* check that the remaining variables really can be ignored */
1030  for( ; nzi < naggrcontnonzs; ++nzi )
1031  {
1032  SCIP_COL* col;
1033  SCIP_VAR* var;
1034  SCIP_Real bounddist;
1035 
1036  c = aggrcontnonzposs[nzi];
1037  assert(0 <= c && c < ncols);
1038  assert(!SCIPisZero(scip, aggrcoefs[c]));
1039 
1040  col = cols[c];
1041  var = SCIPcolGetVar(col);
1042  assert(varIsContinuous(var));
1043 
1044  bounddist = aggrcontnonzbounddists[nzi];
1045 
1046  SCIPdebugMessage(" -> ignoring col <%s>[%g,%g]: sol=%g, dist=%g\n",
1047  SCIPvarGetName(var), bestcontlbs[SCIPvarGetProbindex(var) - nintvars],
1048  bestcontubs[SCIPvarGetProbindex(var) - nintvars], varsolvals[SCIPvarGetProbindex(var)], bounddist);
1049 
1050  assert(SCIPisEQ(scip, bounddist, getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var)));
1051  assert(bounddist < bestbounddist - sepadata->aggrtol);
1052  }
1053 #endif
1054 
1055  /* abort, if no row can be added to remove an additional active continuous variable */
1056  if( bestcol == NULL )
1057  {
1058  SCIPdebugMessage(" -> abort aggregation: no removable column found\n");
1059  break;
1060  }
1061 
1062  /* Step 3: add row to aggregation */
1063  bestrowpos = SCIProwGetLPPos(bestrow);
1064  SCIPdebugMessage(" -> adding %+g<%s> to eliminate variable <%s> (aggregation %d)\n",
1065  aggrfac, SCIProwGetName(bestrow), SCIPvarGetName(SCIPcolGetVar(bestcol)), naggrs+1);
1066  assert(rowweights[bestrowpos] == 0.0);
1067  assert(!SCIPisZero(scip, aggrfac));
1068 
1069  /* change row's aggregation weight */
1070  rowweights[bestrowpos] = aggrfac;
1071  absaggrfac = REALABS(aggrfac);
1072  maxweight = MAX(maxweight, absaggrfac);
1073  minweight = MIN(minweight, absaggrfac);
1074 
1075  /* decrease score of aggregation row in order to not aggregate it again too soon */
1076  decreaseRowScore(scip, rowlhsscores, rowrhsscores, bestrowpos);
1077 
1078  /* change coefficients of aggregation and update the number of continuous variables */
1079  bestrownonzcols = SCIProwGetCols(bestrow);
1080  bestrownonzcoefs = SCIProwGetVals(bestrow);
1081  nbestrownonzcols = SCIProwGetNLPNonz(bestrow);
1082  ncanceledcontnonzs = 0;
1083  for( c = 0; c < nbestrownonzcols; c++ )
1084  {
1085  SCIP_VAR* var;
1086  int pos;
1087  SCIP_Bool iscont;
1088  SCIP_Bool waszero;
1089  SCIP_Bool iszero;
1090 
1091  var = SCIPcolGetVar(bestrownonzcols[c]);
1092  pos = SCIPcolGetLPPos(bestrownonzcols[c]);
1093  assert(pos >= 0);
1094  assert(!SCIPisZero(scip, bestrownonzcoefs[c]));
1095 
1096  iscont = varIsContinuous(var);
1097  waszero = (aggrcoefs[pos] == 0.0);
1098  aggrcoefs[pos] += bestrownonzcoefs[c] * aggrfac;
1099  iszero = SCIPisZero(scip, aggrcoefs[pos]);
1100 
1101  if( iszero )
1102  {
1103  aggrcoefs[pos] = 0.0;
1104  if( !waszero )
1105  {
1106  /* coefficient switched from non-zero to zero */
1107  if( iscont )
1108  {
1109  ncanceledcontnonzs++;
1110  /* naggrcontnonzs will be decreased later in a cleanup step */
1111  updateNActiveConts(scip, varsolvals, bestcontlbs, bestcontubs, nintvars, var, -1, &nactiveconts);
1112  }
1113  else
1114  naggrintnonzs--;
1115  }
1116  }
1117  else if( waszero )
1118  {
1119  /* coefficient switched from zero to non-zero */
1120  if( iscont )
1121  {
1122  SCIP_Real bounddist;
1123 
1124  assert(naggrcontnonzs < ncols);
1125 
1126  /* store continuous variable in array sorted by distance to closest bound */
1127  bounddist = getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var);
1128  SCIPsortedvecInsertDownRealInt(aggrcontnonzbounddists, aggrcontnonzposs, bounddist, pos, &naggrcontnonzs, NULL);
1129 
1130  updateNActiveConts(scip, varsolvals, bestcontlbs, bestcontubs, nintvars, var, +1, &nactiveconts);
1131  }
1132  else
1133  naggrintnonzs++;
1134  }
1135  }
1136 
1137  /* remove canceled elements from aggtcontnonzs vector */
1138  if( ncanceledcontnonzs > 0 )
1139  {
1140  int newnaggrintnonzs;
1141 
1142  newnaggrintnonzs = 0;
1143  for( nzi = 0; nzi < naggrcontnonzs; ++nzi )
1144  {
1145  int pos;
1146 
1147  pos = aggrcontnonzposs[nzi];
1148  assert(0 <= pos && pos < ncols);
1149  if( aggrcoefs[pos] != 0.0 )
1150  {
1151  assert(newnaggrintnonzs <= nzi);
1152  aggrcontnonzposs[newnaggrintnonzs] = pos;
1153  aggrcontnonzbounddists[newnaggrintnonzs] = aggrcontnonzbounddists[nzi];
1154  newnaggrintnonzs++;
1155  }
1156  }
1157  assert(ncanceledcontnonzs == naggrcontnonzs - newnaggrintnonzs);
1158  naggrcontnonzs = newnaggrintnonzs;
1159  }
1160 
1161  naggrs++;
1162 
1163  SCIPdebugMessage(" -> %d continuous variables left (%d/%d active), %d/%d nonzeros, %d/%d aggregations\n",
1164  naggrcontnonzs, nactiveconts, maxconts, naggrcontnonzs + naggrintnonzs, maxaggrnonzs, naggrs, maxaggrs);
1165  }
1166 #ifdef SCIP_DEBUG
1167  if( nactiveconts > maxconts )
1168  {
1169  SCIPdebugMessage(" -> abort aggregation: %d/%d active continuous variables\n", nactiveconts, maxconts);
1170  }
1171  if( naggrcontnonzs + naggrintnonzs > maxaggrnonzs )
1172  {
1173  SCIPdebugMessage(" -> abort aggregation: %d/%d nonzeros\n", naggrcontnonzs + naggrintnonzs, maxaggrnonzs);
1174  }
1175 #endif
1176 
1177  /* free datastructures */
1178  SCIPfreeBufferArray(scip, &rowweights);
1179  SCIPfreeBufferArray(scip, &aggrcontnonzbounddists);
1180  SCIPfreeBufferArray(scip, &aggrcontnonzposs);
1181  SCIPfreeBufferArray(scip, &aggrcoefs);
1182 
1183  return SCIP_OKAY;
1184 }
1185 
1186 /** searches and adds c-MIR cuts that separate the given primal solution */
1187 static
1189  SCIP* scip, /**< SCIP data structure */
1190  SCIP_SEPA* sepa, /**< the c-MIR separator */
1191  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
1192  SCIP_RESULT* result /**< pointer to store the result */
1193  )
1194 {
1195  SCIP_SEPADATA* sepadata;
1196  SCIP_VAR** vars;
1197  SCIP_Real* varsolvals;
1198  SCIP_Real* bestcontlbs;
1199  SCIP_Real* bestcontubs;
1200  SCIP_Real* contvarscorebounds;
1201  SCIP_ROW** rows;
1202  SCIP_Real* rowlhsscores;
1203  SCIP_Real* rowrhsscores;
1204  SCIP_Real* rowscores;
1205  int* roworder;
1206  SCIP_Real maxslack;
1207  SCIP_Real objnorm;
1208  SCIP_Bool cutoff = FALSE;
1209  int nvars;
1210  int nintvars;
1211  int ncontvars;
1212  int nrows;
1213  int ntries;
1214  int nfails;
1215  int depth;
1216  int ncalls;
1217  int maxtries;
1218  int maxfails;
1219  int maxaggrs;
1220  int maxsepacuts;
1221  int maxconts;
1222  int ncuts;
1223  int r;
1224  int v;
1225 
1226  assert(result != NULL);
1227  assert(*result == SCIP_DIDNOTRUN);
1228 
1229  sepadata = SCIPsepaGetData(sepa);
1230  assert(sepadata != NULL);
1231 
1232  depth = SCIPgetDepth(scip);
1233  ncalls = SCIPsepaGetNCallsAtNode(sepa);
1234 
1235  /* only call the cmir cut separator a given number of times at each node */
1236  if( (depth == 0 && sepadata->maxroundsroot >= 0 && ncalls >= sepadata->maxroundsroot)
1237  || (depth > 0 && sepadata->maxrounds >= 0 && ncalls >= sepadata->maxrounds) )
1238  return SCIP_OKAY;
1239 
1240  /* get all rows and number of columns */
1241  SCIP_CALL( SCIPgetLPRowsData(scip, &rows, &nrows) );
1242  assert(nrows == 0 || rows != NULL);
1243 
1244  /* nothing to do, if LP is empty */
1245  if( nrows == 0 )
1246  return SCIP_OKAY;
1247 
1248  /* check whether SCIP was stopped in the meantime */
1249  if( SCIPisStopped(scip) )
1250  return SCIP_OKAY;
1251 
1252  /* get active problem variables */
1253  vars = SCIPgetVars(scip);
1254  nvars = SCIPgetNVars(scip);
1255  ncontvars = SCIPgetNContVars(scip);
1256 #ifdef IMPLINTSARECONT
1257  ncontvars += SCIPgetNImplVars(scip); /* also aggregate out implicit integers */
1258 #endif
1259  nintvars = nvars-ncontvars;
1260  assert(nvars == 0 || vars != NULL);
1261 
1262  /* nothing to do, if problem has no variables */
1263  if( nvars == 0 )
1264  return SCIP_OKAY;
1265 
1266  SCIPdebugMessage("separating c-MIR cuts\n");
1267 
1268  *result = SCIP_DIDNOTFIND;
1269 
1270  /* get data structure */
1271  SCIP_CALL( SCIPallocBufferArray(scip, &rowlhsscores, nrows) );
1272  SCIP_CALL( SCIPallocBufferArray(scip, &rowrhsscores, nrows) );
1273  SCIP_CALL( SCIPallocBufferArray(scip, &rowscores, nrows) );
1274  SCIP_CALL( SCIPallocBufferArray(scip, &roworder, nrows) );
1275  SCIP_CALL( SCIPallocBufferArray(scip, &varsolvals, nvars) );
1276  SCIP_CALL( SCIPallocBufferArray(scip, &bestcontlbs, ncontvars) );
1277  SCIP_CALL( SCIPallocBufferArray(scip, &bestcontubs, ncontvars) );
1278  SCIP_CALL( SCIPallocBufferArray(scip, &contvarscorebounds, ncontvars) );
1279 
1280  /* get the solution values for all active variables */
1281  SCIP_CALL( SCIPgetSolVals(scip, sol, nvars, vars, varsolvals) );
1282 
1283  /* calculate the tightest bounds w.r.t. current solution for the continuous variables */
1284  for( v = nintvars; v < nvars; ++v )
1285  {
1286  SCIP_Real bestlb;
1287  SCIP_Real bestub;
1288  SCIP_Real bestvlb;
1289  SCIP_Real bestvub;
1290  int bestvlbidx;
1291  int bestvubidx;
1292 
1293 #if ALLOWLOCAL == 1
1294  bestlb = SCIPvarGetLbLocal(vars[v]);
1295  bestub = SCIPvarGetUbLocal(vars[v]);
1296 #else
1297  bestlb = SCIPvarGetLbGlobal(vars[v]);
1298  bestub = SCIPvarGetUbGlobal(vars[v]);
1299 #endif
1300  SCIP_CALL( SCIPgetVarClosestVlb(scip, vars[v], sol, &bestvlb, &bestvlbidx) );
1301  SCIP_CALL( SCIPgetVarClosestVub(scip, vars[v], sol, &bestvub, &bestvubidx) );
1302  if( bestvlbidx >= 0 )
1303  bestlb = MAX(bestlb, bestvlb);
1304  if( bestvubidx >= 0 )
1305  bestub = MIN(bestub, bestvub);
1306 
1307  bestcontlbs[v-nintvars] = bestlb;
1308  bestcontubs[v-nintvars] = bestub;
1309 
1310  /* initialize row score bounds for continuous variables */
1311  contvarscorebounds[v-nintvars] = SCIP_REAL_MAX;
1312  }
1313 
1314  /* get the maximal number of cuts allowed in a separation round */
1315  if( depth == 0 )
1316  {
1317  maxtries = sepadata->maxtriesroot;
1318  maxfails = sepadata->maxfailsroot;
1319  maxaggrs = sepadata->maxaggrsroot;
1320  maxsepacuts = sepadata->maxsepacutsroot;
1321  maxslack = sepadata->maxslackroot;
1322  maxconts = sepadata->maxcontsroot;
1323  }
1324  else
1325  {
1326  maxtries = sepadata->maxtries;
1327  maxfails = sepadata->maxfails;
1328  maxaggrs = sepadata->maxaggrs;
1329  maxsepacuts = sepadata->maxsepacuts;
1330  maxslack = sepadata->maxslack;
1331  maxconts = sepadata->maxconts;
1332  }
1333 
1334  /* calculate aggregation scores for both sides of all rows, and sort rows by nonincreasing maximal score */
1335  objnorm = SCIPgetObjNorm(scip);
1336  objnorm = MAX(objnorm, 1.0);
1337  for( r = 0; r < nrows; r++ )
1338  {
1339  int nnonz;
1340  int i;
1341 
1342  assert(SCIProwGetLPPos(rows[r]) == r);
1343 
1344  nnonz = SCIProwGetNLPNonz(rows[r]);
1345  if( nnonz == 0 )
1346  {
1347  /* ignore empty rows */
1348  rowlhsscores[r] = 0.0;
1349  rowrhsscores[r] = 0.0;
1350  }
1351  else
1352  {
1353  SCIP_Real activity;
1354  SCIP_Real lhs;
1355  SCIP_Real rhs;
1356  SCIP_Real dualsol;
1357  SCIP_Real dualscore;
1358  SCIP_Real rowdensity;
1359  SCIP_Real rownorm;
1360  SCIP_Real slack;
1361 
1362  dualsol = (sol == NULL ? SCIProwGetDualsol(rows[r]) : 1.0);
1363  activity = SCIPgetRowSolActivity(scip, rows[r], sol);
1364  lhs = SCIProwGetLhs(rows[r]);
1365  rhs = SCIProwGetRhs(rows[r]);
1366  rownorm = SCIProwGetNorm(rows[r]);
1367  rownorm = MAX(rownorm, 0.1);
1368  rowdensity = (SCIP_Real)(nnonz - sepadata->densityoffset)/(SCIP_Real)nvars;
1369  assert(SCIPisPositive(scip, rownorm));
1370 
1371  slack = (activity - lhs)/rownorm;
1372  dualscore = MAX(dualsol/objnorm, 0.0001);
1373  if( !SCIPisInfinity(scip, -lhs) && SCIPisLE(scip, slack, maxslack)
1374  && (ALLOWLOCAL || !SCIProwIsLocal(rows[r])) /*lint !e506 !e774*/
1375  && rowdensity <= sepadata->maxrowdensity
1376  && rowdensity <= sepadata->maxaggdensity ) /*lint !e774*/
1377  {
1378  rowlhsscores[r] = dualscore + sepadata->densityscore * (1.0-rowdensity)
1379  + sepadata->slackscore * MAX(1.0 - slack, 0.0);
1380  assert(rowlhsscores[r] > 0.0);
1381  }
1382  else
1383  rowlhsscores[r] = 0.0;
1384 
1385  slack = (rhs - activity)/rownorm;
1386  dualscore = MAX(-dualsol/objnorm, 0.0001);
1387  if( !SCIPisInfinity(scip, rhs) && SCIPisLE(scip, slack, maxslack)
1388  && (ALLOWLOCAL || !SCIProwIsLocal(rows[r])) /*lint !e506 !e774*/
1389  && rowdensity <= sepadata->maxrowdensity
1390  && rowdensity <= sepadata->maxaggdensity ) /*lint !e774*/
1391  {
1392  rowrhsscores[r] = dualscore + sepadata->densityscore * (1.0-rowdensity)
1393  + sepadata->slackscore * MAX(1.0 - slack, 0.0);
1394  assert(rowrhsscores[r] > 0.0);
1395  }
1396  else
1397  rowrhsscores[r] = 0.0;
1398  }
1399  rowscores[r] = MAX(rowlhsscores[r], rowrhsscores[r]);
1400  for( i = r; i > 0 && rowscores[r] > rowscores[roworder[i-1]]; --i )
1401  roworder[i] = roworder[i-1];
1402  assert(0 <= i && i <= r);
1403  roworder[i] = r;
1404 
1405  SCIPdebugMessage(" -> row %d <%s>: lhsscore=%g rhsscore=%g maxscore=%g\n", r, SCIProwGetName(rows[r]),
1406  rowlhsscores[r], rowrhsscores[r], rowscores[r]);
1407  }
1408 
1409  /* start aggregation heuristic for each row in the LP */
1410  ncuts = 0;
1411  if( maxtries < 0 )
1412  maxtries = INT_MAX;
1413  if( maxfails < 0 )
1414  maxfails = INT_MAX;
1415  else if( depth == 0 && 2*SCIPgetNSepaRounds(scip) < maxfails )
1416  maxfails += maxfails - 2*SCIPgetNSepaRounds(scip); /* allow up to double as many fails in early separounds of root node */
1417  ntries = 0;
1418  nfails = 0;
1419  for( r = 0; r < nrows && ntries < maxtries && ncuts < maxsepacuts && rowscores[roworder[r]] > 0.0
1420  && !SCIPisStopped(scip); r++ )
1421  {
1422  SCIP_Bool wastried;
1423  int oldncuts;
1424 
1425  oldncuts = ncuts;
1426  SCIP_CALL( aggregation(scip, sepa, sepadata, sol, varsolvals, bestcontlbs, bestcontubs, contvarscorebounds,
1427  rowlhsscores, rowrhsscores, roworder[r], maxaggrs, maxslack, maxconts, &wastried, &cutoff, &ncuts) );
1428  if ( cutoff )
1429  break;
1430 
1431  if( !wastried )
1432  continue;
1433  ntries++;
1434 
1435  if( ncuts == oldncuts )
1436  {
1437  nfails++;
1438  if( nfails >= maxfails )
1439  break;
1440  }
1441  else
1442  nfails = 0;
1443  }
1444 
1445  /* free data structure */
1446  SCIPfreeBufferArray(scip, &contvarscorebounds);
1447  SCIPfreeBufferArray(scip, &bestcontubs);
1448  SCIPfreeBufferArray(scip, &bestcontlbs);
1449  SCIPfreeBufferArray(scip, &varsolvals);
1450  SCIPfreeBufferArray(scip, &roworder);
1451  SCIPfreeBufferArray(scip, &rowscores);
1452  SCIPfreeBufferArray(scip, &rowrhsscores);
1453  SCIPfreeBufferArray(scip, &rowlhsscores);
1454 
1455  if ( cutoff )
1456  *result = SCIP_CUTOFF;
1457  else if ( ncuts > 0 )
1458  *result = SCIP_SEPARATED;
1459 
1460  return SCIP_OKAY;
1461 }
1462 
1463 
1464 /*
1465  * Callback methods of separator
1466  */
1467 
1468 /** copy method for separator plugins (called when SCIP copies plugins) */
1469 static
1470 SCIP_DECL_SEPACOPY(sepaCopyCmir)
1471 { /*lint --e{715}*/
1472  assert(scip != NULL);
1473  assert(sepa != NULL);
1474  assert(strcmp(SCIPsepaGetName(sepa), SEPA_NAME) == 0);
1475 
1476  /* call inclusion method of constraint handler */
1477  SCIP_CALL( SCIPincludeSepaCmir(scip) );
1478 
1479  return SCIP_OKAY;
1480 }
1481 
1482 /** destructor of separator to free user data (called when SCIP is exiting) */
1483 static
1484 SCIP_DECL_SEPAFREE(sepaFreeCmir)
1485 { /*lint --e{715}*/
1486  SCIP_SEPADATA* sepadata;
1487 
1488  /* free separator data */
1489  sepadata = SCIPsepaGetData(sepa);
1490  assert(sepadata != NULL);
1491 
1492  SCIPfreeMemory(scip, &sepadata);
1493 
1494  SCIPsepaSetData(sepa, NULL);
1495 
1496  return SCIP_OKAY;
1497 }
1498 
1499 
1500 /** LP solution separation method of separator */
1501 static
1502 SCIP_DECL_SEPAEXECLP(sepaExeclpCmir)
1503 { /*lint --e{715}*/
1504 
1505  *result = SCIP_DIDNOTRUN;
1506 
1507  /* only call separator, if we are not close to terminating */
1508  if( SCIPisStopped(scip) )
1509  return SCIP_OKAY;
1510 
1511  /* only call separator, if an optimal LP solution is at hand */
1513  return SCIP_OKAY;
1514 
1515  /* only call separator, if there are fractional variables */
1516  if( SCIPgetNLPBranchCands(scip) == 0 )
1517  return SCIP_OKAY;
1518 
1519  SCIP_CALL( separateCuts(scip, sepa, NULL, result) );
1520 
1521  return SCIP_OKAY;
1522 }
1523 
1524 
1525 /** arbitrary primal solution separation method of separator */
1526 static
1527 SCIP_DECL_SEPAEXECSOL(sepaExecsolCmir)
1528 { /*lint --e{715}*/
1529 
1530  *result = SCIP_DIDNOTRUN;
1531 
1532  SCIP_CALL( separateCuts(scip, sepa, sol, result) );
1533 
1534  return SCIP_OKAY;
1535 }
1536 
1537 
1538 /*
1539  * separator specific interface methods
1540  */
1541 
1542 /** creates the cmir separator and includes it in SCIP */
1544  SCIP* scip /**< SCIP data structure */
1545  )
1546 {
1547  SCIP_SEPADATA* sepadata;
1548  SCIP_SEPA* sepa;
1549 
1550  /* create cmir separator data */
1551  SCIP_CALL( SCIPallocMemory(scip, &sepadata) );
1552 
1553  /* include separator */
1556  sepaExeclpCmir, sepaExecsolCmir,
1557  sepadata) );
1558 
1559  assert(sepa != NULL);
1560 
1561  /* set non-NULL pointers to callback methods */
1562  SCIP_CALL( SCIPsetSepaCopy(scip, sepa, sepaCopyCmir) );
1563  SCIP_CALL( SCIPsetSepaFree(scip, sepa, sepaFreeCmir) );
1564 
1565  /* add cmir separator parameters */
1566  SCIP_CALL( SCIPaddIntParam(scip,
1567  "separating/cmir/maxrounds",
1568  "maximal number of cmir separation rounds per node (-1: unlimited)",
1569  &sepadata->maxrounds, FALSE, DEFAULT_MAXROUNDS, -1, INT_MAX, NULL, NULL) );
1570  SCIP_CALL( SCIPaddIntParam(scip,
1571  "separating/cmir/maxroundsroot",
1572  "maximal number of cmir separation rounds in the root node (-1: unlimited)",
1573  &sepadata->maxroundsroot, FALSE, DEFAULT_MAXROUNDSROOT, -1, INT_MAX, NULL, NULL) );
1574  SCIP_CALL( SCIPaddIntParam(scip,
1575  "separating/cmir/maxtries",
1576  "maximal number of rows to start aggregation with per separation round (-1: unlimited)",
1577  &sepadata->maxtries, TRUE, DEFAULT_MAXTRIES, -1, INT_MAX, NULL, NULL) );
1578  SCIP_CALL( SCIPaddIntParam(scip,
1579  "separating/cmir/maxtriesroot",
1580  "maximal number of rows to start aggregation with per separation round in the root node (-1: unlimited)",
1581  &sepadata->maxtriesroot, TRUE, DEFAULT_MAXTRIESROOT, -1, INT_MAX, NULL, NULL) );
1582  SCIP_CALL( SCIPaddIntParam(scip,
1583  "separating/cmir/maxfails",
1584  "maximal number of consecutive unsuccessful aggregation tries (-1: unlimited)",
1585  &sepadata->maxfails, TRUE, DEFAULT_MAXFAILS, -1, INT_MAX, NULL, NULL) );
1586  SCIP_CALL( SCIPaddIntParam(scip,
1587  "separating/cmir/maxfailsroot",
1588  "maximal number of consecutive unsuccessful aggregation tries in the root node (-1: unlimited)",
1589  &sepadata->maxfailsroot, TRUE, DEFAULT_MAXFAILSROOT, -1, INT_MAX, NULL, NULL) );
1590  SCIP_CALL( SCIPaddIntParam(scip,
1591  "separating/cmir/maxaggrs",
1592  "maximal number of aggregations for each row per separation round",
1593  &sepadata->maxaggrs, TRUE, DEFAULT_MAXAGGRS, 0, INT_MAX, NULL, NULL) );
1594  SCIP_CALL( SCIPaddIntParam(scip,
1595  "separating/cmir/maxaggrsroot",
1596  "maximal number of aggregations for each row per separation round in the root node",
1597  &sepadata->maxaggrsroot, TRUE, DEFAULT_MAXAGGRSROOT, 0, INT_MAX, NULL, NULL) );
1598  SCIP_CALL( SCIPaddIntParam(scip,
1599  "separating/cmir/maxsepacuts",
1600  "maximal number of cmir cuts separated per separation round",
1601  &sepadata->maxsepacuts, FALSE, DEFAULT_MAXSEPACUTS, 0, INT_MAX, NULL, NULL) );
1602  SCIP_CALL( SCIPaddIntParam(scip,
1603  "separating/cmir/maxsepacutsroot",
1604  "maximal number of cmir cuts separated per separation round in the root node",
1605  &sepadata->maxsepacutsroot, FALSE, DEFAULT_MAXSEPACUTSROOT, 0, INT_MAX, NULL, NULL) );
1607  "separating/cmir/maxslack",
1608  "maximal slack of rows to be used in aggregation",
1609  &sepadata->maxslack, TRUE, DEFAULT_MAXSLACK, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1611  "separating/cmir/maxslackroot",
1612  "maximal slack of rows to be used in aggregation in the root node",
1613  &sepadata->maxslackroot, TRUE, DEFAULT_MAXSLACKROOT, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1615  "separating/cmir/densityscore",
1616  "weight of row density in the aggregation scoring of the rows",
1617  &sepadata->densityscore, TRUE, DEFAULT_DENSITYSCORE, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1619  "separating/cmir/slackscore",
1620  "weight of slack in the aggregation scoring of the rows",
1621  &sepadata->slackscore, TRUE, DEFAULT_SLACKSCORE, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1623  "separating/cmir/maxaggdensity",
1624  "maximal density of aggregated row",
1625  &sepadata->maxaggdensity, TRUE, DEFAULT_MAXAGGDENSITY, 0.0, 1.0, NULL, NULL) );
1627  "separating/cmir/maxrowdensity",
1628  "maximal density of row to be used in aggregation",
1629  &sepadata->maxrowdensity, TRUE, DEFAULT_MAXROWDENSITY, 0.0, 1.0, NULL, NULL) );
1630  SCIP_CALL( SCIPaddIntParam(scip,
1631  "separating/cmir/densityoffset",
1632  "additional number of variables allowed in row on top of density",
1633  &sepadata->densityoffset, TRUE, DEFAULT_DENSITYOFFSET, 0, INT_MAX, NULL, NULL) );
1635  "separating/cmir/maxrowfac",
1636  "maximal row aggregation factor",
1637  &sepadata->maxrowfac, TRUE, DEFAULT_MAXROWFAC, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1638  SCIP_CALL( SCIPaddIntParam(scip,
1639  "separating/cmir/maxtestdelta",
1640  "maximal number of different deltas to try (-1: unlimited)",
1641  &sepadata->maxtestdelta, TRUE, DEFAULT_MAXTESTDELTA, -1, INT_MAX, NULL, NULL) );
1642  SCIP_CALL( SCIPaddIntParam(scip,
1643  "separating/cmir/maxconts",
1644  "maximal number of active continuous variables in aggregated row",
1645  &sepadata->maxconts, TRUE, DEFAULT_MAXCONTS, 0, INT_MAX, NULL, NULL) );
1646  SCIP_CALL( SCIPaddIntParam(scip,
1647  "separating/cmir/maxcontsroot",
1648  "maximal number of active continuous variables in aggregated row in the root node",
1649  &sepadata->maxcontsroot, TRUE, DEFAULT_MAXCONTSROOT, 0, INT_MAX, NULL, NULL) );
1651  "separating/cmir/aggrtol",
1652  "tolerance for bound distances used to select continuous variable in current aggregated constraint to be eliminated",
1653  &sepadata->aggrtol, TRUE, DEFAULT_AGGRTOL, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1655  "separating/cmir/trynegscaling",
1656  "should negative values also be tested in scaling?",
1657  &sepadata->trynegscaling, TRUE, DEFAULT_TRYNEGSCALING, NULL, NULL) );
1659  "separating/cmir/fixintegralrhs",
1660  "should an additional variable be complemented if f0 = 0?",
1661  &sepadata->fixintegralrhs, TRUE, DEFAULT_FIXINTEGRALRHS, NULL, NULL) );
1663  "separating/cmir/dynamiccuts",
1664  "should generated cuts be removed from the LP if they are no longer tight?",
1665  &sepadata->dynamiccuts, FALSE, DEFAULT_DYNAMICCUTS, NULL, NULL) );
1666 
1667  return SCIP_OKAY;
1668 }
1669