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-2016 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
281 void updateNActiveConts(
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
315 void decreaseRowScore(
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 maxweight, /**< largest magnitude of weights; set to -1 if sparsity information is unknown */
341  int* weightinds, /**< sparsity pattern of weights; size nrowinds; NULL if sparsity info is unknown */
342  int nweightinds, /**< number of nonzeros in weights; -1 if rowinds is NULL */
343  int rowlensum, /**< total number of non-zeros in used rows (row associated with nonzero weight coefficient); -1 if unknown */
344  SCIP_Real* cutcoefs, /**< array to store the cut coefficients */
345  SCIP_Real* mksetcoefs, /**< array to store mixed knapsack set coefficients: size nvars; or NULL */
346  SCIP_Bool* mksetcoefsvalid, /**< pointer to store whether mixed knapsack set coefficients are valid; or NULL */
347  SCIP_Real* testeddeltas, /**< array with already tested deltas */
348  int* ntesteddeltas, /**< pointer to the number of elements in testeddeltas */
349  SCIP_Real delta, /**< delta value to scale mixed knapsack equation with */
350  SCIP_Real boundswitch, /**< fraction of domain up to which lower bound is used in transformation */
351  SCIP_Bool usevbds, /**< should variable bounds be used in bound transformation? */
352  SCIP_Bool allowlocal, /**< should local information allowed to be used, resulting in a local cut? */
353  SCIP_Bool fixintegralrhs, /**< should complementation tried to be adjusted such that rhs gets fractional? */
354  int maxmksetcoefs, /**< maximal number of nonzeros allowed in aggregated base inequality */
355  SCIP_Real maxweightrange, /**< maximal valid range max(|weights|)/min(|weights|) of row weights */
356  SCIP_Real minfrac, /**< minimal fractionality of rhs to produce MIR cut for */
357  SCIP_Real maxfrac, /**< maximal fractionality of rhs to produce MIR cut for */
358  SCIP_Real* bestdelta, /**< pointer to the currently best delta value */
359  SCIP_Real* bestefficacy /**< pointer to the currently best efficacy */
360  )
361 {
362  SCIP_Bool tested;
363  int i;
364 
365  assert(testeddeltas != NULL);
366  assert(ntesteddeltas != NULL);
367  assert(bestdelta != NULL);
368  assert(bestefficacy != NULL);
369 
370  /* do not use too small deltas */
371  if( SCIPisFeasZero(scip, delta) )
372  return SCIP_OKAY;
373 
374  /* check, if delta with mult was already tested */
375  tested = FALSE;
376  for( i = 0; i < *ntesteddeltas && !tested; i++ )
377  tested = SCIPisEQ(scip, testeddeltas[i], delta);
378  if( !tested )
379  {
380  SCIP_Real cutact;
381  SCIP_Real cutrhs;
382  SCIP_Bool success;
383  SCIP_Bool cutislocal;
384 
385  testeddeltas[*ntesteddeltas] = delta;
386  (*ntesteddeltas)++;
387 
388  /* create a MIR cut out of the weighted LP rows */
389  SCIP_CALL( SCIPcalcMIR(scip, sol, boundswitch, usevbds, allowlocal, fixintegralrhs, NULL, NULL, maxmksetcoefs,
390  maxweightrange, minfrac, maxfrac, rowweights, maxweight, weightinds, nweightinds, rowlensum, NULL, delta,
391  mksetcoefs, mksetcoefsvalid, cutcoefs, &cutrhs, &cutact, &success, &cutislocal, NULL) );
392  assert(allowlocal || !cutislocal);
393  SCIPdebugMessage("delta = %g -> success: %u, cutact: %g, cutrhs: %g, vio: %g\n",
394  delta, success, success ? cutact : 0.0, success ? cutrhs : 0.0, success ? cutact - cutrhs : 0.0);
395 
396  /* check if delta generates cut which is more violated */
397  if( success && SCIPisFeasGT(scip, cutact, cutrhs) )
398  {
399  SCIP_Real norm;
400 
401  norm = SCIPgetVectorEfficacyNorm(scip, cutcoefs, nvars);
402  if( norm > 0.0 )
403  {
404  SCIP_Real efficacy;
405 
406  efficacy = (cutact - cutrhs)/norm;
407  SCIPdebugMessage("act = %g rhs = %g eff = %g, old besteff = %g, old bestdelta=%g\n",
408  cutact, cutrhs, efficacy, *bestefficacy, *bestdelta);
409  if( efficacy > *bestefficacy )
410  {
411  *bestdelta = delta;
412  *bestefficacy = efficacy;
413  }
414  }
415  }
416  }
417 
418  return SCIP_OKAY;
419 }
420 
421 /** Performs the cut generation heuristic of the c-MIR separation algorithm, i.e., tries to generate a c-MIR cut which is
422  * valid for the mixed knapsack set corresponding to the current aggregated constraint. Cuts will only be added here if
423  * no pointer to store best scaling factor delta is given.
424  */
426  SCIP* scip, /**< SCIP data structure */
427  SCIP_SEPA* sepa, /**< separator */
428  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
429  SCIP_Real* varsolvals, /**< LP solution value of all variables in LP */
430  int maxtestdelta, /**< maximal number of different deltas to try (-1: unlimited) */
431  SCIP_Real* rowweights, /**< weight of rows in aggregated row */
432  SCIP_Real maxweight, /**< largest magnitude of weights; set to -1.0 if sparsity information is
433  * unknown */
434  int* weightinds, /**< sparsity pattern of weights; size nrowinds; NULL if sparsity info is
435  * unknown */
436  int nweightinds, /**< number of nonzeros in weights; -1 if rowinds is NULL */
437  int rowlensum, /**< total number of non-zeros in used rows (row associated with nonzero weight coefficient); -1 if unknown */
438  SCIP_Real boundswitch, /**< fraction of domain up to which lower bound is used in transformation */
439  SCIP_Bool usevbds, /**< should variable bounds be used in bound transformation? */
440  SCIP_Bool allowlocal, /**< should local information allowed to be used, resulting in a local cut? */
441  SCIP_Bool fixintegralrhs, /**< should complementation tried to be adjusted such that rhs gets fractional? */
442  int maxmksetcoefs, /**< maximal number of nonzeros allowed in aggregated base inequality */
443  SCIP_Real maxweightrange, /**< maximal valid range max(|weights|)/min(|weights|) of row weights */
444  SCIP_Real minfrac, /**< minimal fractionality of rhs to produce MIR cut for */
445  SCIP_Real maxfrac, /**< maximal fractionality of rhs to produce MIR cut for */
446  SCIP_Bool trynegscaling, /**< should negative values also be tested in scaling? */
447  SCIP_Bool cutremovable, /**< should the cut be removed from the LP due to aging or cleanup? */
448  const char* cutclassname, /**< name of cut class to use for row names */
449  SCIP_Bool* cutoff, /**< whether a cutoff has been detected */
450  int* ncuts, /**< pointer to count the number of generated cuts */
451  SCIP_Real* delta, /**< pointer to store best delta found; NULL, if cut should be added here */
452  SCIP_Bool* deltavalid /**< pointer to store whether best delta value is valid or NULL */
453  )
454 { /*lint --e{715}*/
455  SCIP_VAR** vars;
456  SCIP_Real* cutcoefs;
457  SCIP_Real* mksetcoefs;
458  SCIP_Real* testeddeltas;
459  SCIP_Real bestdelta;
460  SCIP_Real bestefficacy;
461  SCIP_Real maxabsmksetcoef;
462  SCIP_Bool mksetcoefsvalid;
463  int nvars;
464  int ncontvars;
465  int nintvars;
466  int ntesteddeltas;
467  int vi;
468 
469  assert( cutoff != NULL );
470  *cutoff = FALSE;
471 
472  if( maxtestdelta == -1 )
473  maxtestdelta = INT_MAX;
474 
475  if( delta != NULL )
476  *deltavalid = FALSE;
477 
478  /* get active problem variables */
479  vars = SCIPgetVars(scip);
480  nvars = SCIPgetNVars(scip);
481  ncontvars = SCIPgetNContVars(scip);
482  nintvars = nvars-ncontvars;
483  if( nvars == 0 )
484  return SCIP_OKAY;
485  assert(vars != NULL);
486 
487  /* get temporary memory */
488  SCIP_CALL( SCIPallocBufferArray(scip, &mksetcoefs, nvars) );
489  SCIP_CALL( SCIPallocBufferArray(scip, &cutcoefs, nvars) );
490  SCIP_CALL( SCIPallocBufferArray(scip, &testeddeltas, 3 + 2*(nintvars+2)) );
491 
492  /* As in Marchand's version. Use the absolute value of the coefficients of the integer variables (lying
493  * strictly between its bounds) in the constructed mixed knapsack set, i.e.,
494  * N* = { |alpha'_j| : j in N, alpha'_j != 0 and l_j < x*_j < u_j }
495  */
496 
497  /* search delta for generating a cut with maximum efficacy:
498  * delta = coefficient of integer variable in constructed mixed knapsack set which lies between its bounds
499  */
500  ntesteddeltas = 0;
501  bestdelta = 0.0;
502  bestefficacy = 0.0;
503  maxabsmksetcoef = 0.0;
504  mksetcoefsvalid = FALSE;
505 
506  /* try delta = 1 and get the coefficients of all variables in the constructed mixed knapsack set;
507  * if the aggregated row contains too many nonzero elements the generation of the c-MIR cut is aborted,
508  * in this case, mksetcoefs is not valid and we can abort the separation heuristic (as the number of nonzeros
509  * keeps the same for different values of delta)
510  */
511  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, maxweight, weightinds, nweightinds, rowlensum, cutcoefs, mksetcoefs,
512  &mksetcoefsvalid, testeddeltas, &ntesteddeltas, 1.0, boundswitch, usevbds, allowlocal, fixintegralrhs,
513  maxmksetcoefs, maxweightrange, minfrac, maxfrac, &bestdelta, &bestefficacy) );
514  if( mksetcoefsvalid && trynegscaling )
515  {
516  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, maxweight, weightinds, nweightinds, rowlensum, cutcoefs, NULL,
517  NULL, testeddeltas, &ntesteddeltas, -1.0, boundswitch, usevbds, allowlocal, fixintegralrhs, maxmksetcoefs,
518  maxweightrange, minfrac, maxfrac, &bestdelta, &bestefficacy) );
519  }
520 
521  /* find mult in { +1, -1 } and delta in the corresponding set N* leading to the most violated c-MIR cut */
522  for( vi = 0; mksetcoefsvalid && vi < nintvars; vi++ )
523  {
524  SCIP_VAR* var;
525  SCIP_Real primsol;
526  SCIP_Real lb;
527  SCIP_Real ub;
528  SCIP_Real absmksetcoef;
529 
530  var = vars[vi];
531  assert(vi == SCIPvarGetProbindex(var));
532  assert(SCIPvarGetType(var) != SCIP_VARTYPE_CONTINUOUS);
533  assert(SCIPvarIsActive(var));
534  assert(SCIPvarIsIntegral(var));
535 
536  /* update maximum coefficient of integer variables in constructed mixed knapsack set for
537  * mult = +1 and delta = 1 and
538  * mult = -1 and delta = 1
539  */
540  absmksetcoef = REALABS(mksetcoefs[vi]);
541  maxabsmksetcoef = MAX(maxabsmksetcoef, absmksetcoef);
542 
543  if( ntesteddeltas >= maxtestdelta )
544  continue; /* remaining loop is only for maxabsmksetcoef calculation */
545 
546  /* ignore variables with current solution value on its bounds */
547  primsol = varsolvals[vi];
548  lb = SCIPvarGetLbLocal(var);
549  ub = SCIPvarGetUbLocal(var);
550  if( SCIPisEQ(scip, primsol, lb) || SCIPisEQ(scip, primsol, ub) )
551  continue;
552 
553  /* try to divide aggregated row by absmksetcoef */
554  if( !SCIPisFeasZero(scip, absmksetcoef) )
555  {
556  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, maxweight, weightinds, nweightinds, rowlensum, cutcoefs, NULL,
557  NULL, testeddeltas, &ntesteddeltas, 1.0/absmksetcoef, boundswitch, usevbds, allowlocal, fixintegralrhs,
558  maxmksetcoefs, maxweightrange, minfrac, maxfrac, &bestdelta, &bestefficacy) );
559  if( trynegscaling )
560  {
561  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, maxweight, weightinds, nweightinds, rowlensum, cutcoefs,
562  NULL, NULL, testeddeltas, &ntesteddeltas, -1.0/absmksetcoef, boundswitch, usevbds, allowlocal,
563  fixintegralrhs, maxmksetcoefs, maxweightrange, minfrac, maxfrac, &bestdelta, &bestefficacy) );
564  }
565  }
566  }
567 
568  /* additionally try delta = maxabscoef+1 */
569  if( mksetcoefsvalid && !SCIPisFeasZero(scip, maxabsmksetcoef) )
570  {
571  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, maxweight, weightinds, nweightinds, rowlensum, cutcoefs, NULL,
572  NULL, testeddeltas, &ntesteddeltas, 1.0/(maxabsmksetcoef+1.0), boundswitch, usevbds, allowlocal,
573  fixintegralrhs, maxmksetcoefs, maxweightrange, minfrac, maxfrac, &bestdelta, &bestefficacy) );
574  if( trynegscaling )
575  {
576  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, maxweight, weightinds, nweightinds, rowlensum, cutcoefs, NULL,
577  NULL, testeddeltas, &ntesteddeltas, -1.0/(maxabsmksetcoef+1.0), boundswitch, usevbds, allowlocal,
578  fixintegralrhs, maxmksetcoefs, maxweightrange, minfrac, maxfrac, &bestdelta, &bestefficacy) );
579  }
580  }
581 
582  /* delta found */
583  if( mksetcoefsvalid && SCIPisEfficacious(scip, bestefficacy) )
584  {
585  SCIP_Real currentdelta;
586  SCIP_Real cutrhs;
587  SCIP_Real cutact;
588  SCIP_Bool success;
589  SCIP_Bool cutislocal;
590  int cutrank;
591  int i;
592 
593  assert(!SCIPisFeasZero(scip, bestdelta));
594 
595  /* Try to improve efficacy by multiplying delta with 2, 4 and 8 */
596  for( i = 0, currentdelta = 2.0 * bestdelta; i < 3; i++, currentdelta *= 2.0 )
597  {
598  SCIP_CALL( tryDelta(scip, sol, nvars, rowweights, maxweight, weightinds, nweightinds, rowlensum, cutcoefs,
599  NULL, NULL, testeddeltas, &ntesteddeltas, currentdelta, boundswitch, usevbds, allowlocal, fixintegralrhs,
600  maxmksetcoefs, maxweightrange, minfrac, maxfrac, &bestdelta, &bestefficacy) );
601  }
602 
603  /* if no pointer to store delta is given, add cut here (zerohalf cuts will be stored in a separate cut pool first) */
604  if( delta == NULL )
605  {
606  /* generate cut with bestdelta and best boundswitch value */
607  SCIP_CALL( SCIPcalcMIR(scip, sol, boundswitch, usevbds, allowlocal, fixintegralrhs, NULL, NULL,
608  maxmksetcoefs, maxweightrange, minfrac, maxfrac, rowweights, maxweight, weightinds, nweightinds, rowlensum,
609  NULL, bestdelta, NULL, NULL, cutcoefs, &cutrhs, &cutact, &success, &cutislocal, &cutrank) );
610  assert(allowlocal || !cutislocal);
611  assert(success);
612 
613  /* add the cut to the separation storage */
614  SCIP_CALL( addCut(scip, sepa, sol, varsolvals, cutcoefs, cutrhs, cutislocal, cutremovable, cutrank, cutclassname, cutoff, ncuts) );
615  }
616  else
617  {
618  *delta = bestdelta;
619  *deltavalid = TRUE;
620  }
621  }
622 
623  /* free datastructures */
624  SCIPfreeBufferArray(scip, &testeddeltas);
625  SCIPfreeBufferArray(scip, &cutcoefs);
626  SCIPfreeBufferArray(scip, &mksetcoefs);
627 
628  return SCIP_OKAY;
629 }
630 
631 /** returns whether the variable should be tried to be aggregated out */
632 static
634  SCIP_VAR* var /**< problem variable */
635  )
636 {
637  SCIP_VARTYPE vartype;
638 
639  vartype = SCIPvarGetType(var);
640 
641 #ifdef IMPLINTSARECONT
642  return (vartype == SCIP_VARTYPE_CONTINUOUS || vartype == SCIP_VARTYPE_IMPLINT);
643 #else
644  return (vartype == SCIP_VARTYPE_CONTINUOUS);
645 #endif
646 }
647 
648 /** returns the minimal distance of the solution of a continuous variable to its bounds */
649 static
651  SCIP* scip, /**< SCIP data structure */
652  int nintvars, /**< number of integer variables in the problem */
653  SCIP_Real* varsolvals, /**< LP solution value of all variables in LP */
654  SCIP_Real* bestcontlbs, /**< best lower (variable or standard) bounds of continuous variables */
655  SCIP_Real* bestcontubs, /**< best upper (variable or standard) bounds of continuous variables */
656  SCIP_VAR* var /**< continuous variable to get bound distance for */
657  )
658 {
659  SCIP_Real primsol;
660  SCIP_Real lb;
661  SCIP_Real ub;
662  SCIP_Real distlower;
663  SCIP_Real distupper;
664  SCIP_Real bounddist;
665 
666  assert(varIsContinuous(var));
667  assert(SCIPvarGetProbindex(var) >= nintvars);
668 
669  primsol = varsolvals[SCIPvarGetProbindex(var)];
670  lb = bestcontlbs[SCIPvarGetProbindex(var) - nintvars];
671  ub = bestcontubs[SCIPvarGetProbindex(var) - nintvars];
672  assert(SCIPisGE(scip, lb, SCIPvarGetLbGlobal(var)));
673  assert(SCIPisLE(scip, ub, SCIPvarGetUbGlobal(var)));
674  distlower = primsol - lb;
675  distupper = ub - primsol;
676  bounddist = MIN(distlower, distupper);
677 
678 #ifdef IMPLINTSARECONT
679  /* prefer continuous variables over implicit integers to be aggregated out */
681  bounddist /= 10.0;
682 #endif
683 
684  return bounddist;
685 }
686 
687 /** aggregates different single mixed integer constraints by taking linear combinations of the rows of the LP */
688 static
690  SCIP* scip, /**< SCIP data structure */
691  SCIP_SEPA* sepa, /**< separator */
692  SCIP_SEPADATA* sepadata, /**< separator data */
693  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
694  SCIP_Real* varsolvals, /**< LP solution value of all variables in LP */
695  SCIP_Real* bestcontlbs, /**< best lower (variable or standard) bounds of continuous variables */
696  SCIP_Real* bestcontubs, /**< best upper (variable or standard) bounds of continuous variables */
697  SCIP_Real* contvarscorebounds, /**< bounds on the maximal rowlhsscores and rowrhsscores the variable is contained in */
698  SCIP_Real* rowlhsscores, /**< aggregation scores for left hand sides of row */
699  SCIP_Real* rowrhsscores, /**< aggregation scores for right hand sides of row */
700  int startrow, /**< index of row to start aggregation */
701  int maxaggrs, /**< maximal number of aggregations */
702  SCIP_Real maxslack, /**< maximal slack of rows to be used in aggregation */
703  int maxconts, /**< maximal number of active continuous variables in aggregated row */
704  SCIP_Bool* wastried, /**< pointer to store whether the given startrow was actually tried */
705  SCIP_Bool* cutoff, /**< whether a cutoff has been detected */
706  int* ncuts /**< pointer to count the number of generated cuts */
707  )
708 {
709  SCIP_COL** startnonzcols;
710  SCIP_COL** cols;
711  SCIP_VAR** vars;
712  SCIP_ROW** rows;
713  SCIP_COL* bestcol;
714  SCIP_Real* startnonzcoefs;
715  SCIP_Real* aggrcoefs;
716  SCIP_Real* rowweights;
717  int* weightinds;
718  int* aggrcontnonzposs;
719  SCIP_Real* aggrcontnonzbounddists;
720  SCIP_Real maxweight;
721  SCIP_Real minweight;
722  SCIP_Real startrowact;
723  SCIP_Bool hasfractional;
724  int naggrintnonzs;
725  int naggrcontnonzs;
726  int maxaggrnonzs;
727  int nstartnonzcols;
728  int naggrs;
729  int nactiveconts;
730  int nvars;
731  int nintvars;
732  int ncontvars;
733  int ncols;
734  int nrows;
735  int indpos;
736  int c;
737  int r;
738  int nweightinds;
739  int rowlensum;
740 
741  assert(scip != NULL);
742  assert(sepadata != NULL);
743  assert(varsolvals != NULL);
744  assert(rowlhsscores != NULL);
745  assert(rowrhsscores != NULL);
746  assert(wastried != NULL);
747  assert(cutoff != NULL);
748  assert(ncuts != NULL);
749 
750  *cutoff = FALSE;
751  *wastried = FALSE;
752 
753  SCIP_CALL( SCIPgetVarsData(scip, &vars, &nvars, NULL, NULL, NULL, &ncontvars) );
754 #ifdef IMPLINTSARECONT
755  ncontvars += SCIPgetNImplVars(scip); /* also aggregate out implicit integers */
756 #endif
757  nintvars = nvars - ncontvars;
758  assert((nvars == 0 && nintvars == 0 && ncontvars == 0) || vars != NULL);
759  SCIP_CALL( SCIPgetLPColsData(scip, &cols, &ncols) );
760  assert(ncols == 0 || cols != NULL);
761  SCIP_CALL( SCIPgetLPRowsData(scip, &rows, &nrows) );
762  assert(nrows == 0 || rows != NULL);
763  assert(0 <= startrow && startrow < nrows);
764 
765  SCIPdebugMessage("start c-MIR aggregation with row <%s> (%d/%d)\n", SCIProwGetName(rows[startrow]), startrow, nrows);
766 
767  /* calculate maximal number of non-zeros in aggregated row */
768  maxaggrnonzs = (int)(sepadata->maxaggdensity * ncols) + sepadata->densityoffset;
769 
770  /* get temporary memory */
771  SCIP_CALL( SCIPallocBufferArray(scip, &aggrcoefs, ncols) );
772  BMSclearMemoryArray(aggrcoefs, ncols);
773  SCIP_CALL( SCIPallocBufferArray(scip, &aggrcontnonzposs, ncols) );
774  SCIP_CALL( SCIPallocBufferArray(scip, &aggrcontnonzbounddists, ncols) );
775  SCIP_CALL( SCIPallocBufferArray(scip, &rowweights, nrows) );
776  /* initialize weights of rows in aggregation */
777  BMSclearMemoryArray(rowweights, nrows);
778  SCIP_CALL( SCIPallocBufferArray(scip, &weightinds, nrows) );
779  BMSclearMemoryArray(weightinds, nrows);
780 
781  startrowact = SCIPgetRowSolActivity(scip, rows[startrow], sol);
782  if( startrowact <= 0.5 * SCIProwGetLhs(rows[startrow]) + 0.5 * SCIProwGetRhs(rows[startrow]) )
783  rowweights[startrow] = -1.0;
784  else
785  rowweights[startrow] = 1.0;
786 
787  /* build weights sparse representation */
788  nweightinds = 0;
789  rowlensum = 0;
790  weightinds[nweightinds] = startrow;
791  nweightinds++;
792  rowlensum += SCIProwGetNNonz(rows[startrow]);
793 
794  maxweight = 1.0;
795  minweight = 1.0;
796 
797  /* get nonzero columns and coefficients of startrow */
798  startnonzcols = SCIProwGetCols(rows[startrow]);
799  nstartnonzcols = SCIProwGetNLPNonz(rows[startrow]);
800  startnonzcoefs = SCIProwGetVals(rows[startrow]);
801 
802  /* for all columns of startrow store coefficient as coefficient in aggregated row */
803  naggrintnonzs = 0;
804  naggrcontnonzs = 0;
805  nactiveconts = 0;
806  hasfractional = FALSE;
807  for( c = 0; c < nstartnonzcols; c++ )
808  {
809  SCIP_VAR* var;
810  int pos;
811 
812  var = SCIPcolGetVar(startnonzcols[c]);
813  pos = SCIPcolGetLPPos(startnonzcols[c]);
814  assert(pos >= 0);
815  assert(!SCIPisZero(scip, startnonzcoefs[c]));
816  aggrcoefs[pos] = rowweights[startrow] * startnonzcoefs[c];
817  if( varIsContinuous(var) )
818  {
819  SCIP_Real bounddist;
820 
821  updateNActiveConts(scip, varsolvals, bestcontlbs, bestcontubs, nintvars, var, +1, &nactiveconts);
822 
823  /* store continuous variable in array sorted by distance to closest bound */
824  bounddist = getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var);
825  SCIPsortedvecInsertDownRealInt(aggrcontnonzbounddists, aggrcontnonzposs, bounddist, pos, &naggrcontnonzs, NULL);
826  }
827  else
828  naggrintnonzs++;
829 
830  if( !hasfractional && SCIPvarIsIntegral(var) )
831  {
832  SCIP_Real primsol;
833 
834  primsol = varsolvals[SCIPvarGetProbindex(var)];
835  hasfractional = !SCIPisFeasIntegral(scip, primsol);
836  }
837  }
838  assert(naggrintnonzs + naggrcontnonzs == nstartnonzcols);
839 
840  /* don't try aggregation if there is no integer variable with fractional value */
841  if( !hasfractional )
842  {
843  SCIPdebugMessage(" -> row has no fractional integer variables: ignore\n");
844  maxaggrs = -1;
845  }
846 
847  /* decrease score of startrow in order to not aggregate it again too soon */
848  decreaseRowScore(scip, rowlhsscores, rowrhsscores, startrow);
849 
850  /* try to generate cut from the current aggregated row
851  * add cut if found, otherwise add another row to aggregated row
852  * in order to get rid of a continuous variable
853  */
854  naggrs = 0;
855  while( nactiveconts <= maxconts && naggrs <= maxaggrs && naggrcontnonzs + naggrintnonzs <= maxaggrnonzs )
856  {
857  SCIP_ROW* bestrow;
858  SCIP_COL** bestrownonzcols; /* columns with nonzero coefficients in best row to add */
859  SCIP_Real* bestrownonzcoefs; /* nonzero coefficients of columns in best row to add */
860  int nbestrownonzcols; /* number of columns with nonzero coefficients in best row to add */
861  SCIP_Real bestbounddist;
862  SCIP_Real bestscore;
863  int bestrowpos;
864  SCIP_Real aggrfac;
865  SCIP_Real absaggrfac;
866  int nzi;
867  int oldncuts;
868  int ncanceledcontnonzs;
869 
870  *wastried = TRUE;
871 
872 #ifdef SCIP_DEBUG
873  SCIPdebugMessage("aggregation of startrow %d and %d additional rows with %d integer and %d continuous variables (%d active):\n",
874  startrow, naggrs, naggrintnonzs, naggrcontnonzs, nactiveconts);
875  for( c = 0; c < ncols; ++c )
876  {
877  if( aggrcoefs[c] != 0.0 )
878  SCIPdebugPrintf(" %+g<%s>(%g)", aggrcoefs[c], SCIPvarGetName(SCIPcolGetVar(cols[c])),
879  varsolvals[SCIPvarGetProbindex(SCIPcolGetVar(cols[c]))]);
880  }
881  SCIPdebugPrintf("\n");
882 #endif
883 
884  /* Step 1:
885  * try to generate a MIR cut out of the current aggregation
886  */
887  oldncuts = *ncuts;
888  SCIP_CALL( SCIPcutGenerationHeuristicCmir(scip, sepa, sol, varsolvals, sepadata->maxtestdelta, rowweights, maxweight,
889  weightinds, nweightinds, rowlensum, BOUNDSWITCH, USEVBDS, ALLOWLOCAL, sepadata->fixintegralrhs,
890  (int) MAXAGGRLEN(nvars), sepadata->maxrowfac, MINFRAC, MAXFRAC, sepadata->trynegscaling,
891  sepadata->dynamiccuts, "cmir", cutoff, ncuts, NULL, NULL) );
892 
893  if ( *cutoff )
894  break;
895 
896  /* if the cut was successfully added, abort the aggregation of further rows */
897  if( *ncuts > oldncuts )
898  {
899  SCIPdebugMessage(" -> abort aggregation: cut found\n");
900  break;
901  }
902 
903  /* Step 2:
904  * aggregate an additional row in order to remove a continuous variable
905  */
906 
907  /* abort, if we reached the maximal number of aggregations */
908  if( naggrs == maxaggrs )
909  {
910  SCIPdebugMessage(" -> abort aggregation: %s\n", nactiveconts == 0 ? "no more active continuous variables"
911  : "maximal number of aggregations reached");
912  break;
913  }
914 
915  SCIPdebugMessage(" -> search column to eliminate\n");
916 
917  /* search for "best" continuous variable in aggregated row:
918  * - solution value is strictly between lower and upper bound
919  * - it exists a not yet aggregated row with nonzero coefficient in this column
920  * out of these variables:
921  * - prefer variables with larger distance of current solution value to its bounds
922  * - of those with large bound distance, prefer variables that can be eliminated with a row of high score
923  */
924  bestcol = NULL;
925  bestbounddist = -1.0;
926  bestscore = 0.0;
927  bestrow = NULL;
928  aggrfac = 0.0;
929  for( nzi = 0; nzi < naggrcontnonzs; ++nzi )
930  {
931  SCIP_COL* col;
932  SCIP_VAR* var;
933  SCIP_Real bounddist;
934 
935  c = aggrcontnonzposs[nzi];
936  assert(0 <= c && c < ncols);
937  assert(!SCIPisZero(scip, aggrcoefs[c]));
938 
939  col = cols[c];
940  var = SCIPcolGetVar(col);
941  assert(varIsContinuous(var));
942  assert(SCIPvarGetProbindex(var) >= nintvars);
943 
944  bounddist = aggrcontnonzbounddists[nzi];
945  assert(SCIPisEQ(scip, bounddist, getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var)));
946  assert(bounddist <= bestbounddist || bestbounddist == -1.0);
947 
948  /* check, if variable is candidate to be the new best variable */
949  if( bounddist >= bestbounddist - sepadata->aggrtol )
950  {
951  SCIP_ROW** nonzrows;
952  SCIP_Real* nonzcoefs;
953  SCIP_Real maxrowscore;
954  int nnonzrows;
955  int probindex;
956 
957  probindex = SCIPvarGetProbindex(var);
958  assert(probindex >= nintvars);
959 
960  SCIPdebugMessage(" -> col <%s>[%g,%g]: sol=%g, dist=%g\n",
961  SCIPvarGetName(var), bestcontlbs[probindex - nintvars],
962  bestcontubs[probindex - nintvars], varsolvals[probindex], bounddist);
963 
964  /* if we know that we will not find a better row, just skip the column */
965  if( contvarscorebounds[probindex - nintvars] <= bestscore )
966  continue;
967 
968  /* look for "best" row to add (minimal slack), but don't add rows again,
969  * that are already involved in aggregation
970  */
971  nnonzrows = SCIPcolGetNLPNonz(col);
972  nonzrows = SCIPcolGetRows(col);
973  nonzcoefs = SCIPcolGetVals(col);
974  maxrowscore = 0.0;
975 
976  for( r = 0; r < nnonzrows; r++ )
977  {
978  SCIP_Real score;
979  SCIP_Real rowscore;
980  SCIP_Real factor;
981  SCIP_Real absfactor;
982  SCIP_Real activity;
983  SCIP_Real lhs;
984  SCIP_Real rhs;
985  SCIP_Real rowlhsscore;
986  SCIP_Real rowrhsscore;
987  int lppos;
988 
989  lppos = SCIProwGetLPPos(nonzrows[r]);
990  assert(0 <= lppos && lppos < nrows);
991 
992  SCIPdebugMessage(" -> r=%d row <%s>: weight=%g, pos=%d, alpha_j=%g, a^r_j=%g, factor=%g, %g <= %g <= %g\n",
993  r, SCIProwGetName(nonzrows[r]), rowweights[lppos], lppos, aggrcoefs[c], nonzcoefs[r],
994  - aggrcoefs[c] / nonzcoefs[r], SCIProwGetLhs(nonzrows[r]),
995  SCIPgetRowSolActivity(scip, nonzrows[r], sol), SCIProwGetRhs(nonzrows[r]));
996 
997  /* update maxrowscore */
998  rowlhsscore = rowlhsscores[lppos];
999  rowrhsscore = rowrhsscores[lppos];
1000  rowscore = MAX(rowlhsscore, rowrhsscore);
1001  maxrowscore = MAX(maxrowscore, rowscore);
1002 
1003  /* if even the better rowscore does not improve the bestscore, ignore the row */
1004  if( rowscore <= bestscore )
1005  continue;
1006 
1007  /* take only unmodifiable LP rows, that are not yet aggregated */
1008  if( rowweights[lppos] != 0.0 || SCIProwIsModifiable(nonzrows[r]) )
1009  continue;
1010 
1011  /* don't aggregate rows that would lead to a too extreme aggregation factor */
1012  factor = - aggrcoefs[c] / nonzcoefs[r];
1013  absfactor = REALABS(factor);
1014  if( !SCIPisPositive(scip, absfactor)
1015  || absfactor > sepadata->maxrowfac * minweight
1016  || maxweight > sepadata->maxrowfac * absfactor )
1017  continue;
1018 
1019  /* for selected real variable y_k, select constraint r with best score SCORE_r with r in P\Q,
1020  * where P\Q is the set of constraints not yet involved in the aggregation set
1021  */
1022  assert(!SCIPisInfinity(scip, -SCIProwGetLhs(nonzrows[r])) || rowlhsscores[lppos] == 0.0);
1023  assert(!SCIPisInfinity(scip, SCIProwGetRhs(nonzrows[r])) || rowrhsscores[lppos] == 0.0);
1024  score = (factor < 0.0 ? rowlhsscore : rowrhsscore);
1025  if( score <= bestscore )
1026  continue;
1027 
1028  /* check, if the row's slack multiplied with the aggregation factor is too large */
1029  activity = SCIPgetRowSolActivity(scip, nonzrows[r], sol);
1030  lhs = SCIProwGetLhs(nonzrows[r]);
1031  rhs = SCIProwGetRhs(nonzrows[r]);
1032  if( (factor < 0.0 && SCIPisGT(scip, factor * (lhs - activity), maxslack))
1033  || (factor > 0.0 && SCIPisGT(scip, factor * (rhs - activity), maxslack)) )
1034  continue;
1035 
1036  /* the row passed all tests: it is the best candidate up to now */
1037  bestbounddist = bounddist;
1038  bestscore = score;
1039  bestcol = col;
1040  bestrow = nonzrows[r];
1041  aggrfac = factor;
1042  SCIPdebugMessage(" -> col <%s>: %g * row <%s>, bounddist=%g, score=%g\n",
1043  SCIPvarGetName(SCIPcolGetVar(bestcol)), aggrfac, SCIProwGetName(bestrow), bestbounddist, score);
1044  }
1045 
1046  /* update score bound of column */
1047  assert(maxrowscore <= contvarscorebounds[probindex - nintvars]);
1048  contvarscorebounds[probindex - nintvars] = maxrowscore;
1049  }
1050  else
1051  {
1052  /* since the nonzero continuous variables are sorted by bound distance, we can abort now */
1053  break;
1054  }
1055  }
1056  assert((bestcol == NULL) == (bestrow == NULL));
1057 
1058 #ifndef NDEBUG
1059  /* check that the remaining variables really can be ignored */
1060  for( ; nzi < naggrcontnonzs; ++nzi )
1061  {
1062  SCIP_COL* col;
1063  SCIP_VAR* var;
1064  SCIP_Real bounddist;
1065 
1066  c = aggrcontnonzposs[nzi];
1067  assert(0 <= c && c < ncols);
1068  assert(!SCIPisZero(scip, aggrcoefs[c]));
1069 
1070  col = cols[c];
1071  var = SCIPcolGetVar(col);
1072  assert(varIsContinuous(var));
1073 
1074  bounddist = aggrcontnonzbounddists[nzi];
1075 
1076  SCIPdebugMessage(" -> ignoring col <%s>[%g,%g]: sol=%g, dist=%g\n",
1077  SCIPvarGetName(var), bestcontlbs[SCIPvarGetProbindex(var) - nintvars],
1078  bestcontubs[SCIPvarGetProbindex(var) - nintvars], varsolvals[SCIPvarGetProbindex(var)], bounddist);
1079 
1080  assert(SCIPisEQ(scip, bounddist, getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var)));
1081  assert(bounddist < bestbounddist - sepadata->aggrtol);
1082  }
1083 #endif
1084 
1085  /* abort, if no row can be added to remove an additional active continuous variable */
1086  if( bestcol == NULL )
1087  {
1088  SCIPdebugMessage(" -> abort aggregation: no removable column found\n");
1089  break;
1090  }
1091 
1092  /* Step 3: add row to aggregation */
1093  bestrowpos = SCIProwGetLPPos(bestrow);
1094  SCIPdebugMessage(" -> adding %+g<%s> to eliminate variable <%s> (aggregation %d)\n",
1095  aggrfac, SCIProwGetName(bestrow), SCIPvarGetName(SCIPcolGetVar(bestcol)), naggrs+1);
1096  assert(rowweights[bestrowpos] == 0.0);
1097  assert(!SCIPisZero(scip, aggrfac));
1098 
1099  /* change row's aggregation weight */
1100  rowweights[bestrowpos] = aggrfac;
1101 
1102  /* build weights sparse representation */
1103  SCIPsortedvecInsertInt(weightinds, bestrowpos, &nweightinds, &indpos);
1104  rowlensum += SCIProwGetNNonz(rows[bestrowpos]);
1105 
1106  absaggrfac = REALABS(aggrfac);
1107  maxweight = MAX(maxweight, absaggrfac);
1108  minweight = MIN(minweight, absaggrfac);
1109 
1110  /* decrease score of aggregation row in order to not aggregate it again too soon */
1111  decreaseRowScore(scip, rowlhsscores, rowrhsscores, bestrowpos);
1112 
1113  /* change coefficients of aggregation and update the number of continuous variables */
1114  bestrownonzcols = SCIProwGetCols(bestrow);
1115  bestrownonzcoefs = SCIProwGetVals(bestrow);
1116  nbestrownonzcols = SCIProwGetNLPNonz(bestrow);
1117  ncanceledcontnonzs = 0;
1118  for( c = 0; c < nbestrownonzcols; c++ )
1119  {
1120  SCIP_VAR* var;
1121  int pos;
1122  SCIP_Bool iscont;
1123  SCIP_Bool waszero;
1124  SCIP_Bool iszero;
1125 
1126  var = SCIPcolGetVar(bestrownonzcols[c]);
1127  pos = SCIPcolGetLPPos(bestrownonzcols[c]);
1128  assert(pos >= 0);
1129  assert(!SCIPisZero(scip, bestrownonzcoefs[c]));
1130 
1131  iscont = varIsContinuous(var);
1132  waszero = (aggrcoefs[pos] == 0.0);
1133  aggrcoefs[pos] += bestrownonzcoefs[c] * aggrfac;
1134  iszero = SCIPisZero(scip, aggrcoefs[pos]);
1135 
1136  if( iszero )
1137  {
1138  aggrcoefs[pos] = 0.0;
1139  if( !waszero )
1140  {
1141  /* coefficient switched from non-zero to zero */
1142  if( iscont )
1143  {
1144  ncanceledcontnonzs++;
1145  /* naggrcontnonzs will be decreased later in a cleanup step */
1146  updateNActiveConts(scip, varsolvals, bestcontlbs, bestcontubs, nintvars, var, -1, &nactiveconts);
1147  }
1148  else
1149  naggrintnonzs--;
1150  }
1151  }
1152  else if( waszero )
1153  {
1154  /* coefficient switched from zero to non-zero */
1155  if( iscont )
1156  {
1157  SCIP_Real bounddist;
1158 
1159  assert(naggrcontnonzs < ncols);
1160 
1161  /* store continuous variable in array sorted by distance to closest bound */
1162  bounddist = getBounddist(scip, nintvars, varsolvals, bestcontlbs, bestcontubs, var);
1163  SCIPsortedvecInsertDownRealInt(aggrcontnonzbounddists, aggrcontnonzposs, bounddist, pos, &naggrcontnonzs, NULL);
1164 
1165  updateNActiveConts(scip, varsolvals, bestcontlbs, bestcontubs, nintvars, var, +1, &nactiveconts);
1166  }
1167  else
1168  naggrintnonzs++;
1169  }
1170  }
1171 
1172  /* remove canceled elements from aggtcontnonzs vector */
1173  if( ncanceledcontnonzs > 0 )
1174  {
1175  int newnaggrintnonzs;
1176 
1177  newnaggrintnonzs = 0;
1178  for( nzi = 0; nzi < naggrcontnonzs; ++nzi )
1179  {
1180  int pos;
1181 
1182  pos = aggrcontnonzposs[nzi];
1183  assert(0 <= pos && pos < ncols);
1184  if( aggrcoefs[pos] != 0.0 )
1185  {
1186  assert(newnaggrintnonzs <= nzi);
1187  aggrcontnonzposs[newnaggrintnonzs] = pos;
1188  aggrcontnonzbounddists[newnaggrintnonzs] = aggrcontnonzbounddists[nzi];
1189  newnaggrintnonzs++;
1190  }
1191  }
1192  assert(ncanceledcontnonzs == naggrcontnonzs - newnaggrintnonzs);
1193  naggrcontnonzs = newnaggrintnonzs;
1194  }
1195 
1196  naggrs++;
1197 
1198  SCIPdebugMessage(" -> %d continuous variables left (%d/%d active), %d/%d nonzeros, %d/%d aggregations\n",
1199  naggrcontnonzs, nactiveconts, maxconts, naggrcontnonzs + naggrintnonzs, maxaggrnonzs, naggrs, maxaggrs);
1200  }
1201 #ifdef SCIP_DEBUG
1202  if( nactiveconts > maxconts )
1203  {
1204  SCIPdebugMessage(" -> abort aggregation: %d/%d active continuous variables\n", nactiveconts, maxconts);
1205  }
1206  if( naggrcontnonzs + naggrintnonzs > maxaggrnonzs )
1207  {
1208  SCIPdebugMessage(" -> abort aggregation: %d/%d nonzeros\n", naggrcontnonzs + naggrintnonzs, maxaggrnonzs);
1209  }
1210 #endif
1211 
1212  /* free datastructures */
1213  SCIPfreeBufferArray(scip, &weightinds);
1214  SCIPfreeBufferArray(scip, &rowweights);
1215  SCIPfreeBufferArray(scip, &aggrcontnonzbounddists);
1216  SCIPfreeBufferArray(scip, &aggrcontnonzposs);
1217  SCIPfreeBufferArray(scip, &aggrcoefs);
1218 
1219  return SCIP_OKAY;
1220 }
1221 
1222 /** searches and adds c-MIR cuts that separate the given primal solution */
1223 static
1225  SCIP* scip, /**< SCIP data structure */
1226  SCIP_SEPA* sepa, /**< the c-MIR separator */
1227  SCIP_SOL* sol, /**< the solution that should be separated, or NULL for LP solution */
1228  SCIP_RESULT* result /**< pointer to store the result */
1229  )
1230 {
1231  SCIP_SEPADATA* sepadata;
1232  SCIP_VAR** vars;
1233  SCIP_Real* varsolvals;
1234  SCIP_Real* bestcontlbs;
1235  SCIP_Real* bestcontubs;
1236  SCIP_Real* contvarscorebounds;
1237  SCIP_ROW** rows;
1238  SCIP_Real* rowlhsscores;
1239  SCIP_Real* rowrhsscores;
1240  SCIP_Real* rowscores;
1241  int* roworder;
1242  SCIP_Real maxslack;
1243  SCIP_Real objnorm;
1244  SCIP_Bool cutoff = FALSE;
1245  int nvars;
1246  int nintvars;
1247  int ncontvars;
1248  int nrows;
1249  int nnonzrows;
1250  int zerorows;
1251  int ntries;
1252  int nfails;
1253  int depth;
1254  int ncalls;
1255  int maxtries;
1256  int maxfails;
1257  int maxaggrs;
1258  int maxsepacuts;
1259  int maxconts;
1260  int ncuts;
1261  int r;
1262  int v;
1263 
1264  assert(result != NULL);
1265  assert(*result == SCIP_DIDNOTRUN);
1266 
1267  sepadata = SCIPsepaGetData(sepa);
1268  assert(sepadata != NULL);
1269 
1270  depth = SCIPgetDepth(scip);
1271  ncalls = SCIPsepaGetNCallsAtNode(sepa);
1272 
1273  /* only call the cmir cut separator a given number of times at each node */
1274  if( (depth == 0 && sepadata->maxroundsroot >= 0 && ncalls >= sepadata->maxroundsroot)
1275  || (depth > 0 && sepadata->maxrounds >= 0 && ncalls >= sepadata->maxrounds) )
1276  return SCIP_OKAY;
1277 
1278  /* get all rows and number of columns */
1279  SCIP_CALL( SCIPgetLPRowsData(scip, &rows, &nrows) );
1280  assert(nrows == 0 || rows != NULL);
1281 
1282  /* nothing to do, if LP is empty */
1283  if( nrows == 0 )
1284  return SCIP_OKAY;
1285 
1286  /* check whether SCIP was stopped in the meantime */
1287  if( SCIPisStopped(scip) )
1288  return SCIP_OKAY;
1289 
1290  /* get active problem variables */
1291  vars = SCIPgetVars(scip);
1292  nvars = SCIPgetNVars(scip);
1293  ncontvars = SCIPgetNContVars(scip);
1294 #ifdef IMPLINTSARECONT
1295  ncontvars += SCIPgetNImplVars(scip); /* also aggregate out implicit integers */
1296 #endif
1297  nintvars = nvars-ncontvars;
1298  assert(nvars == 0 || vars != NULL);
1299 
1300  /* nothing to do, if problem has no variables */
1301  if( nvars == 0 )
1302  return SCIP_OKAY;
1303 
1304  SCIPdebugMessage("separating c-MIR cuts\n");
1305 
1306  *result = SCIP_DIDNOTFIND;
1307 
1308  /* get data structure */
1309  SCIP_CALL( SCIPallocBufferArray(scip, &rowlhsscores, nrows) );
1310  SCIP_CALL( SCIPallocBufferArray(scip, &rowrhsscores, nrows) );
1311  SCIP_CALL( SCIPallocBufferArray(scip, &rowscores, nrows) );
1312  SCIP_CALL( SCIPallocBufferArray(scip, &roworder, nrows) );
1313  SCIP_CALL( SCIPallocBufferArray(scip, &varsolvals, nvars) );
1314  SCIP_CALL( SCIPallocBufferArray(scip, &bestcontlbs, ncontvars) );
1315  SCIP_CALL( SCIPallocBufferArray(scip, &bestcontubs, ncontvars) );
1316  SCIP_CALL( SCIPallocBufferArray(scip, &contvarscorebounds, ncontvars) );
1317 
1318  /* get the solution values for all active variables */
1319  SCIP_CALL( SCIPgetSolVals(scip, sol, nvars, vars, varsolvals) );
1320 
1321  /* calculate the tightest bounds w.r.t. current solution for the continuous variables */
1322  for( v = nintvars; v < nvars; ++v )
1323  {
1324  SCIP_Real bestlb;
1325  SCIP_Real bestub;
1326  SCIP_Real bestvlb;
1327  SCIP_Real bestvub;
1328  int bestvlbidx;
1329  int bestvubidx;
1330 
1331 #if ALLOWLOCAL == 1
1332  bestlb = SCIPvarGetLbLocal(vars[v]);
1333  bestub = SCIPvarGetUbLocal(vars[v]);
1334 #else
1335  bestlb = SCIPvarGetLbGlobal(vars[v]);
1336  bestub = SCIPvarGetUbGlobal(vars[v]);
1337 #endif
1338  SCIP_CALL( SCIPgetVarClosestVlb(scip, vars[v], sol, &bestvlb, &bestvlbidx) );
1339  SCIP_CALL( SCIPgetVarClosestVub(scip, vars[v], sol, &bestvub, &bestvubidx) );
1340  if( bestvlbidx >= 0 )
1341  bestlb = MAX(bestlb, bestvlb);
1342  if( bestvubidx >= 0 )
1343  bestub = MIN(bestub, bestvub);
1344 
1345  bestcontlbs[v-nintvars] = bestlb;
1346  bestcontubs[v-nintvars] = bestub;
1347 
1348  /* initialize row score bounds for continuous variables */
1349  contvarscorebounds[v-nintvars] = SCIP_REAL_MAX;
1350  }
1351 
1352  /* get the maximal number of cuts allowed in a separation round */
1353  if( depth == 0 )
1354  {
1355  maxtries = sepadata->maxtriesroot;
1356  maxfails = sepadata->maxfailsroot;
1357  maxaggrs = sepadata->maxaggrsroot;
1358  maxsepacuts = sepadata->maxsepacutsroot;
1359  maxslack = sepadata->maxslackroot;
1360  maxconts = sepadata->maxcontsroot;
1361  }
1362  else
1363  {
1364  maxtries = sepadata->maxtries;
1365  maxfails = sepadata->maxfails;
1366  maxaggrs = sepadata->maxaggrs;
1367  maxsepacuts = sepadata->maxsepacuts;
1368  maxslack = sepadata->maxslack;
1369  maxconts = sepadata->maxconts;
1370  }
1371 
1372  /* calculate aggregation scores for both sides of all rows, and sort rows by nonincreasing maximal score */
1373  objnorm = SCIPgetObjNorm(scip);
1374  objnorm = MAX(objnorm, 1.0);
1375 
1376  /* count the number of non-zero rows and zero rows.
1377  * these values are used for the sorting of the rowscores.
1378  * only the non-zero rows need to be sorted. */
1379  nnonzrows = 0;
1380  zerorows = 0;
1381  for( r = 0; r < nrows; r++ )
1382  {
1383  int nnonz;
1384  int i;
1385 
1386  assert(SCIProwGetLPPos(rows[r]) == r);
1387 
1388  nnonz = SCIProwGetNLPNonz(rows[r]);
1389  if( nnonz == 0 )
1390  {
1391  /* ignore empty rows */
1392  rowlhsscores[r] = 0.0;
1393  rowrhsscores[r] = 0.0;
1394 
1395  /* adding the row number to the back of the roworder
1396  * for the zero rows */
1397  zerorows++;
1398  rowscores[r] = 0.0;
1399  roworder[nrows - zerorows] = r;
1400  }
1401  else
1402  {
1403  SCIP_Real activity;
1404  SCIP_Real lhs;
1405  SCIP_Real rhs;
1406  SCIP_Real dualsol;
1407  SCIP_Real dualscore;
1408  SCIP_Real rowdensity;
1409  SCIP_Real rownorm;
1410  SCIP_Real slack;
1411 
1412  dualsol = (sol == NULL ? SCIProwGetDualsol(rows[r]) : 1.0);
1413  activity = SCIPgetRowSolActivity(scip, rows[r], sol);
1414  lhs = SCIProwGetLhs(rows[r]);
1415  rhs = SCIProwGetRhs(rows[r]);
1416  rownorm = SCIProwGetNorm(rows[r]);
1417  rownorm = MAX(rownorm, 0.1);
1418  rowdensity = (SCIP_Real)(nnonz - sepadata->densityoffset)/(SCIP_Real)nvars;
1419  assert(SCIPisPositive(scip, rownorm));
1420 
1421  slack = (activity - lhs)/rownorm;
1422  dualscore = MAX(dualsol/objnorm, 0.0001);
1423  if( !SCIPisInfinity(scip, -lhs) && SCIPisLE(scip, slack, maxslack)
1424  && (ALLOWLOCAL || !SCIProwIsLocal(rows[r])) /*lint !e506 !e774*/
1425  && rowdensity <= sepadata->maxrowdensity
1426  && rowdensity <= sepadata->maxaggdensity ) /*lint !e774*/
1427  {
1428  rowlhsscores[r] = dualscore + sepadata->densityscore * (1.0-rowdensity)
1429  + sepadata->slackscore * MAX(1.0 - slack, 0.0);
1430  assert(rowlhsscores[r] > 0.0);
1431  }
1432  else
1433  rowlhsscores[r] = 0.0;
1434 
1435  slack = (rhs - activity)/rownorm;
1436  dualscore = MAX(-dualsol/objnorm, 0.0001);
1437  if( !SCIPisInfinity(scip, rhs) && SCIPisLE(scip, slack, maxslack)
1438  && (ALLOWLOCAL || !SCIProwIsLocal(rows[r])) /*lint !e506 !e774*/
1439  && rowdensity <= sepadata->maxrowdensity
1440  && rowdensity <= sepadata->maxaggdensity ) /*lint !e774*/
1441  {
1442  rowrhsscores[r] = dualscore + sepadata->densityscore * (1.0-rowdensity)
1443  + sepadata->slackscore * MAX(1.0 - slack, 0.0);
1444  assert(rowrhsscores[r] > 0.0);
1445  }
1446  else
1447  rowrhsscores[r] = 0.0;
1448 
1449  rowscores[r] = MAX(rowlhsscores[r], rowrhsscores[r]);
1450  if( rowscores[r] == 0.0 )
1451  {
1452  /* adding the row number to the back of the roworder
1453  * for the zero rows */
1454  zerorows++;
1455  roworder[nrows - zerorows] = r;
1456  }
1457  else
1458  {
1459  /* adding and sorting the row number to the next index
1460  * in roworder <= nnonzrows */
1461  for( i = nnonzrows; i > 0 && rowscores[r] > rowscores[roworder[i - 1]]; --i )
1462  roworder[i] = roworder[i - 1];
1463  roworder[i] = r;
1464 
1465  nnonzrows++;
1466  }
1467  }
1468 
1469  SCIPdebugMessage(" -> row %d <%s>: lhsscore=%g rhsscore=%g maxscore=%g\n", r, SCIProwGetName(rows[r]),
1470  rowlhsscores[r], rowrhsscores[r], rowscores[r]);
1471  }
1472  assert(nrows == nnonzrows + zerorows);
1473 
1474  /* start aggregation heuristic for each row in the LP */
1475  ncuts = 0;
1476  if( maxtries < 0 )
1477  maxtries = INT_MAX;
1478  if( maxfails < 0 )
1479  maxfails = INT_MAX;
1480  else if( depth == 0 && 2*SCIPgetNSepaRounds(scip) < maxfails )
1481  maxfails += maxfails - 2*SCIPgetNSepaRounds(scip); /* allow up to double as many fails in early separounds of root node */
1482  ntries = 0;
1483  nfails = 0;
1484  for( r = 0; r < nrows && ntries < maxtries && ncuts < maxsepacuts && rowscores[roworder[r]] > 0.0
1485  && !SCIPisStopped(scip); r++ )
1486  {
1487  SCIP_Bool wastried;
1488  int oldncuts;
1489 
1490  oldncuts = ncuts;
1491  SCIP_CALL( aggregation(scip, sepa, sepadata, sol, varsolvals, bestcontlbs, bestcontubs, contvarscorebounds,
1492  rowlhsscores, rowrhsscores, roworder[r], maxaggrs, maxslack, maxconts, &wastried, &cutoff, &ncuts) );
1493  if ( cutoff )
1494  break;
1495 
1496  if( !wastried )
1497  continue;
1498  ntries++;
1499 
1500  if( ncuts == oldncuts )
1501  {
1502  nfails++;
1503  if( nfails >= maxfails )
1504  break;
1505  }
1506  else
1507  nfails = 0;
1508  }
1509 
1510  /* free data structure */
1511  SCIPfreeBufferArray(scip, &contvarscorebounds);
1512  SCIPfreeBufferArray(scip, &bestcontubs);
1513  SCIPfreeBufferArray(scip, &bestcontlbs);
1514  SCIPfreeBufferArray(scip, &varsolvals);
1515  SCIPfreeBufferArray(scip, &roworder);
1516  SCIPfreeBufferArray(scip, &rowscores);
1517  SCIPfreeBufferArray(scip, &rowrhsscores);
1518  SCIPfreeBufferArray(scip, &rowlhsscores);
1519 
1520  if ( cutoff )
1521  *result = SCIP_CUTOFF;
1522  else if ( ncuts > 0 )
1523  *result = SCIP_SEPARATED;
1524 
1525  return SCIP_OKAY;
1526 }
1527 
1528 
1529 /*
1530  * Callback methods of separator
1531  */
1532 
1533 /** copy method for separator plugins (called when SCIP copies plugins) */
1534 static
1535 SCIP_DECL_SEPACOPY(sepaCopyCmir)
1536 { /*lint --e{715}*/
1537  assert(scip != NULL);
1538  assert(sepa != NULL);
1539  assert(strcmp(SCIPsepaGetName(sepa), SEPA_NAME) == 0);
1540 
1541  /* call inclusion method of constraint handler */
1542  SCIP_CALL( SCIPincludeSepaCmir(scip) );
1543 
1544  return SCIP_OKAY;
1545 }
1546 
1547 /** destructor of separator to free user data (called when SCIP is exiting) */
1548 static
1549 SCIP_DECL_SEPAFREE(sepaFreeCmir)
1550 { /*lint --e{715}*/
1551  SCIP_SEPADATA* sepadata;
1552 
1553  /* free separator data */
1554  sepadata = SCIPsepaGetData(sepa);
1555  assert(sepadata != NULL);
1556 
1557  SCIPfreeMemory(scip, &sepadata);
1558 
1559  SCIPsepaSetData(sepa, NULL);
1560 
1561  return SCIP_OKAY;
1562 }
1563 
1564 
1565 /** LP solution separation method of separator */
1566 static
1567 SCIP_DECL_SEPAEXECLP(sepaExeclpCmir)
1568 { /*lint --e{715}*/
1569 
1570  *result = SCIP_DIDNOTRUN;
1572  /* only call separator, if we are not close to terminating */
1573  if( SCIPisStopped(scip) )
1574  return SCIP_OKAY;
1575 
1576  /* only call separator, if an optimal LP solution is at hand */
1578  return SCIP_OKAY;
1579 
1580  /* only call separator, if there are fractional variables */
1581  if( SCIPgetNLPBranchCands(scip) == 0 )
1582  return SCIP_OKAY;
1583 
1584  SCIP_CALL( separateCuts(scip, sepa, NULL, result) );
1585 
1586  return SCIP_OKAY;
1587 }
1588 
1589 
1590 /** arbitrary primal solution separation method of separator */
1591 static
1592 SCIP_DECL_SEPAEXECSOL(sepaExecsolCmir)
1593 { /*lint --e{715}*/
1594 
1595  *result = SCIP_DIDNOTRUN;
1597  SCIP_CALL( separateCuts(scip, sepa, sol, result) );
1598 
1599  return SCIP_OKAY;
1600 }
1601 
1602 
1603 /*
1604  * separator specific interface methods
1605  */
1606 
1607 /** creates the cmir separator and includes it in SCIP */
1609  SCIP* scip /**< SCIP data structure */
1610  )
1611 {
1612  SCIP_SEPADATA* sepadata;
1613  SCIP_SEPA* sepa;
1614 
1615  /* create cmir separator data */
1616  SCIP_CALL( SCIPallocMemory(scip, &sepadata) );
1617 
1618  /* include separator */
1621  sepaExeclpCmir, sepaExecsolCmir,
1622  sepadata) );
1623 
1624  assert(sepa != NULL);
1625 
1626  /* set non-NULL pointers to callback methods */
1627  SCIP_CALL( SCIPsetSepaCopy(scip, sepa, sepaCopyCmir) );
1628  SCIP_CALL( SCIPsetSepaFree(scip, sepa, sepaFreeCmir) );
1629 
1630  /* add cmir separator parameters */
1631  SCIP_CALL( SCIPaddIntParam(scip,
1632  "separating/cmir/maxrounds",
1633  "maximal number of cmir separation rounds per node (-1: unlimited)",
1634  &sepadata->maxrounds, FALSE, DEFAULT_MAXROUNDS, -1, INT_MAX, NULL, NULL) );
1635  SCIP_CALL( SCIPaddIntParam(scip,
1636  "separating/cmir/maxroundsroot",
1637  "maximal number of cmir separation rounds in the root node (-1: unlimited)",
1638  &sepadata->maxroundsroot, FALSE, DEFAULT_MAXROUNDSROOT, -1, INT_MAX, NULL, NULL) );
1639  SCIP_CALL( SCIPaddIntParam(scip,
1640  "separating/cmir/maxtries",
1641  "maximal number of rows to start aggregation with per separation round (-1: unlimited)",
1642  &sepadata->maxtries, TRUE, DEFAULT_MAXTRIES, -1, INT_MAX, NULL, NULL) );
1643  SCIP_CALL( SCIPaddIntParam(scip,
1644  "separating/cmir/maxtriesroot",
1645  "maximal number of rows to start aggregation with per separation round in the root node (-1: unlimited)",
1646  &sepadata->maxtriesroot, TRUE, DEFAULT_MAXTRIESROOT, -1, INT_MAX, NULL, NULL) );
1647  SCIP_CALL( SCIPaddIntParam(scip,
1648  "separating/cmir/maxfails",
1649  "maximal number of consecutive unsuccessful aggregation tries (-1: unlimited)",
1650  &sepadata->maxfails, TRUE, DEFAULT_MAXFAILS, -1, INT_MAX, NULL, NULL) );
1651  SCIP_CALL( SCIPaddIntParam(scip,
1652  "separating/cmir/maxfailsroot",
1653  "maximal number of consecutive unsuccessful aggregation tries in the root node (-1: unlimited)",
1654  &sepadata->maxfailsroot, TRUE, DEFAULT_MAXFAILSROOT, -1, INT_MAX, NULL, NULL) );
1655  SCIP_CALL( SCIPaddIntParam(scip,
1656  "separating/cmir/maxaggrs",
1657  "maximal number of aggregations for each row per separation round",
1658  &sepadata->maxaggrs, TRUE, DEFAULT_MAXAGGRS, 0, INT_MAX, NULL, NULL) );
1659  SCIP_CALL( SCIPaddIntParam(scip,
1660  "separating/cmir/maxaggrsroot",
1661  "maximal number of aggregations for each row per separation round in the root node",
1662  &sepadata->maxaggrsroot, TRUE, DEFAULT_MAXAGGRSROOT, 0, INT_MAX, NULL, NULL) );
1663  SCIP_CALL( SCIPaddIntParam(scip,
1664  "separating/cmir/maxsepacuts",
1665  "maximal number of cmir cuts separated per separation round",
1666  &sepadata->maxsepacuts, FALSE, DEFAULT_MAXSEPACUTS, 0, INT_MAX, NULL, NULL) );
1667  SCIP_CALL( SCIPaddIntParam(scip,
1668  "separating/cmir/maxsepacutsroot",
1669  "maximal number of cmir cuts separated per separation round in the root node",
1670  &sepadata->maxsepacutsroot, FALSE, DEFAULT_MAXSEPACUTSROOT, 0, INT_MAX, NULL, NULL) );
1672  "separating/cmir/maxslack",
1673  "maximal slack of rows to be used in aggregation",
1674  &sepadata->maxslack, TRUE, DEFAULT_MAXSLACK, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1676  "separating/cmir/maxslackroot",
1677  "maximal slack of rows to be used in aggregation in the root node",
1678  &sepadata->maxslackroot, TRUE, DEFAULT_MAXSLACKROOT, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1680  "separating/cmir/densityscore",
1681  "weight of row density in the aggregation scoring of the rows",
1682  &sepadata->densityscore, TRUE, DEFAULT_DENSITYSCORE, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1684  "separating/cmir/slackscore",
1685  "weight of slack in the aggregation scoring of the rows",
1686  &sepadata->slackscore, TRUE, DEFAULT_SLACKSCORE, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1688  "separating/cmir/maxaggdensity",
1689  "maximal density of aggregated row",
1690  &sepadata->maxaggdensity, TRUE, DEFAULT_MAXAGGDENSITY, 0.0, 1.0, NULL, NULL) );
1692  "separating/cmir/maxrowdensity",
1693  "maximal density of row to be used in aggregation",
1694  &sepadata->maxrowdensity, TRUE, DEFAULT_MAXROWDENSITY, 0.0, 1.0, NULL, NULL) );
1695  SCIP_CALL( SCIPaddIntParam(scip,
1696  "separating/cmir/densityoffset",
1697  "additional number of variables allowed in row on top of density",
1698  &sepadata->densityoffset, TRUE, DEFAULT_DENSITYOFFSET, 0, INT_MAX, NULL, NULL) );
1700  "separating/cmir/maxrowfac",
1701  "maximal row aggregation factor",
1702  &sepadata->maxrowfac, TRUE, DEFAULT_MAXROWFAC, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1703  SCIP_CALL( SCIPaddIntParam(scip,
1704  "separating/cmir/maxtestdelta",
1705  "maximal number of different deltas to try (-1: unlimited)",
1706  &sepadata->maxtestdelta, TRUE, DEFAULT_MAXTESTDELTA, -1, INT_MAX, NULL, NULL) );
1707  SCIP_CALL( SCIPaddIntParam(scip,
1708  "separating/cmir/maxconts",
1709  "maximal number of active continuous variables in aggregated row",
1710  &sepadata->maxconts, TRUE, DEFAULT_MAXCONTS, 0, INT_MAX, NULL, NULL) );
1711  SCIP_CALL( SCIPaddIntParam(scip,
1712  "separating/cmir/maxcontsroot",
1713  "maximal number of active continuous variables in aggregated row in the root node",
1714  &sepadata->maxcontsroot, TRUE, DEFAULT_MAXCONTSROOT, 0, INT_MAX, NULL, NULL) );
1716  "separating/cmir/aggrtol",
1717  "tolerance for bound distances used to select continuous variable in current aggregated constraint to be eliminated",
1718  &sepadata->aggrtol, TRUE, DEFAULT_AGGRTOL, 0.0, SCIP_REAL_MAX, NULL, NULL) );
1720  "separating/cmir/trynegscaling",
1721  "should negative values also be tested in scaling?",
1722  &sepadata->trynegscaling, TRUE, DEFAULT_TRYNEGSCALING, NULL, NULL) );
1724  "separating/cmir/fixintegralrhs",
1725  "should an additional variable be complemented if f0 = 0?",
1726  &sepadata->fixintegralrhs, TRUE, DEFAULT_FIXINTEGRALRHS, NULL, NULL) );
1728  "separating/cmir/dynamiccuts",
1729  "should generated cuts be removed from the LP if they are no longer tight?",
1730  &sepadata->dynamiccuts, FALSE, DEFAULT_DYNAMICCUTS, NULL, NULL) );
1731 
1732  return SCIP_OKAY;
1733 }
enum SCIP_Result SCIP_RESULT
Definition: type_result.h:51
int SCIPgetNLPBranchCands(SCIP *scip)
Definition: scip.c:33158
SCIP_Bool SCIPisEQ(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
Definition: scip.c:41572
SCIP_Bool SCIPisZero(SCIP *scip, SCIP_Real val)
Definition: scip.c:41685
static SCIP_DECL_SEPAEXECSOL(sepaExecsolCmir)
Definition: sepa_cmir.c:1596
int SCIPgetNVars(SCIP *scip)
Definition: scip.c:10698
#define SCIPallocMemory(scip, ptr)
Definition: scip.h:20526
void SCIPsortedvecInsertDownRealInt(SCIP_Real *realarray, int *intarray, SCIP_Real keyval, int field1val, int *len, int *pos)
static void decreaseRowScore(SCIP *scip, SCIP_Real *rowlhsscores, SCIP_Real *rowrhsscores, int rowidx)
Definition: sepa_cmir.c:319
const char * SCIPvarGetName(SCIP_VAR *var)
Definition: var.c:16443
#define USEVBDS
Definition: sepa_cmir.c:74
SCIP_Real SCIPgetRowSolActivity(SCIP *scip, SCIP_ROW *row, SCIP_SOL *sol)
Definition: scip.c:28285
SCIP_RETCODE SCIPcalcMIR(SCIP *scip, SCIP_SOL *sol, SCIP_Real boundswitch, SCIP_Bool usevbds, SCIP_Bool allowlocal, SCIP_Bool fixintegralrhs, int *boundsfortrans, SCIP_BOUNDTYPE *boundtypesfortrans, int maxmksetcoefs, SCIP_Real maxweightrange, SCIP_Real minfrac, SCIP_Real maxfrac, SCIP_Real *weights, SCIP_Real maxweight, int *weightinds, int nweightinds, int rowlensum, int *sidetypes, SCIP_Real scale, SCIP_Real *mksetcoefs, SCIP_Bool *mksetcoefsvalid, SCIP_Real *mircoef, SCIP_Real *mirrhs, SCIP_Real *cutactivity, SCIP_Bool *success, SCIP_Bool *cutislocal, int *cutrank)
Definition: scip.c:27058
SCIP_Bool SCIPisInfinity(SCIP *scip, SCIP_Real val)
Definition: scip.c:41648
SCIP_Real SCIPgetObjNorm(SCIP *scip)
Definition: scip.c:10351
SCIP_RETCODE SCIPgetVarClosestVlb(SCIP *scip, SCIP_VAR *var, SCIP_SOL *sol, SCIP_Real *closestvlb, int *closestvlbidx)
Definition: scip.c:21511
SCIP_Real SCIPgetRowMinCoef(SCIP *scip, SCIP_ROW *row)
Definition: scip.c:28045
static void updateNActiveConts(SCIP *scip, SCIP_Real *varsolvals, SCIP_Real *bestcontlbs, SCIP_Real *bestcontubs, int nintvars, SCIP_VAR *var, int delta, int *nactiveconts)
Definition: sepa_cmir.c:285
SCIP_VAR ** SCIPgetVars(SCIP *scip)
Definition: scip.c:10653
#define SCIP_MAXSTRLEN
Definition: def.h:201
SCIP_Bool SCIPisEfficacious(SCIP *scip, SCIP_Real efficacy)
Definition: scip.c:30877
#define NULL
Definition: lpi_spx.cpp:130
SCIP_Real SCIPvarGetLbLocal(SCIP_VAR *var)
Definition: var.c:17113
SCIP_Bool SCIPisStopped(SCIP *scip)
Definition: scip.c:1125
SCIP_Real SCIProwGetLhs(SCIP_ROW *row)
Definition: lp.c:18915
SCIP_COL ** SCIProwGetCols(SCIP_ROW *row)
Definition: lp.c:18861
SCIP_Real SCIPvarGetUbGlobal(SCIP_VAR *var)
Definition: var.c:17067
SCIP_Bool SCIPisCutEfficacious(SCIP *scip, SCIP_SOL *sol, SCIP_ROW *cut)
Definition: scip.c:30859
static SCIP_DECL_SEPACOPY(sepaCopyCmir)
Definition: sepa_cmir.c:1539
#define DEFAULT_MAXCONTS
Definition: sepa_cmir.c:64
int SCIProwGetNLPNonz(SCIP_ROW *row)
Definition: lp.c:18850
#define FALSE
Definition: def.h:56
#define DEFAULT_TRYNEGSCALING
Definition: sepa_cmir.c:69
int SCIPsnprintf(char *t, int len, const char *s,...)
Definition: misc.c:8174
#define TRUE
Definition: def.h:55
enum SCIP_Retcode SCIP_RETCODE
Definition: type_retcode.h:53
#define SCIP_CALL(x)
Definition: def.h:266
#define DEFAULT_SLACKSCORE
Definition: sepa_cmir.c:58
#define MAXAGGRLEN(nvars)
Definition: sepa_cmir.c:81
SCIP_Bool SCIPisFeasZero(SCIP *scip, SCIP_Real val)
Definition: scip.c:41972
#define SEPA_USESSUBSCIP
Definition: sepa_cmir.c:36
#define DEFAULT_MAXFAILS
Definition: sepa_cmir.c:47
SCIP_Bool SCIPisFeasIntegral(SCIP *scip, SCIP_Real val)
Definition: scip.c:42008
SCIP_RETCODE SCIPaddVarsToRow(SCIP *scip, SCIP_ROW *row, int nvars, SCIP_VAR **vars, SCIP_Real *vals)
Definition: scip.c:27888
static SCIP_RETCODE tryDelta(SCIP *scip, SCIP_SOL *sol, int nvars, SCIP_Real *rowweights, SCIP_Real maxweight, int *weightinds, int nweightinds, int rowlensum, SCIP_Real *cutcoefs, SCIP_Real *mksetcoefs, SCIP_Bool *mksetcoefsvalid, SCIP_Real *testeddeltas, int *ntesteddeltas, SCIP_Real delta, SCIP_Real boundswitch, SCIP_Bool usevbds, SCIP_Bool allowlocal, SCIP_Bool fixintegralrhs, int maxmksetcoefs, SCIP_Real maxweightrange, SCIP_Real minfrac, SCIP_Real maxfrac, SCIP_Real *bestdelta, SCIP_Real *bestefficacy)
Definition: sepa_cmir.c:339
static SCIP_Real getBounddist(SCIP *scip, int nintvars, SCIP_Real *varsolvals, SCIP_Real *bestcontlbs, SCIP_Real *bestcontubs, SCIP_VAR *var)
Definition: sepa_cmir.c:654
SCIP_LPSOLSTAT SCIPgetLPSolstat(SCIP *scip)
Definition: scip.c:26439
#define SCIPdebugMessage
Definition: pub_message.h:77
#define DEFAULT_MAXAGGDENSITY
Definition: sepa_cmir.c:59
#define BMSclearMemoryArray(ptr, num)
Definition: memory.h:85
#define MINFRAC
Definition: sepa_cmir.c:76
#define DEFAULT_MAXAGGRS
Definition: sepa_cmir.c:51
int SCIPgetNContVars(SCIP *scip)
Definition: scip.c:10878
SCIP_RETCODE SCIPaddCut(SCIP *scip, SCIP_SOL *sol, SCIP_ROW *cut, SCIP_Bool forcecut, SCIP_Bool *infeasible)
Definition: scip.c:30967
SCIP_RETCODE SCIPsetSepaFree(SCIP *scip, SCIP_SEPA *sepa, SCIP_DECL_SEPAFREE((*sepafree)))
Definition: scip.c:6718
SCIP_SEPADATA * SCIPsepaGetData(SCIP_SEPA *sepa)
Definition: sepa.c:544
const char * SCIPsepaGetName(SCIP_SEPA *sepa)
Definition: sepa.c:633
SCIP_Real SCIPgetRowMaxCoef(SCIP *scip, SCIP_ROW *row)
Definition: scip.c:28063
SCIP_RETCODE SCIPgetLPColsData(SCIP *scip, SCIP_COL ***cols, int *ncols)
Definition: scip.c:26672
#define DEFAULT_FIXINTEGRALRHS
Definition: sepa_cmir.c:70
#define ALLOWLOCAL
Definition: sepa_cmir.c:75
#define DEFAULT_MAXROUNDSROOT
Definition: sepa_cmir.c:40
SCIP_RETCODE SCIPaddBoolParam(SCIP *scip, const char *name, const char *desc, SCIP_Bool *valueptr, SCIP_Bool isadvanced, SCIP_Bool defaultvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip.c:3547
SCIP_RETCODE SCIPaddIntParam(SCIP *scip, const char *name, const char *desc, int *valueptr, SCIP_Bool isadvanced, int defaultvalue, int minvalue, int maxvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip.c:3573
SCIP_Bool SCIPvarIsIntegral(SCIP_VAR *var)
Definition: var.c:16634
int SCIPcolGetLPPos(SCIP_COL *col)
Definition: lp.c:18726
#define SCIPfreeMemory(scip, ptr)
Definition: scip.h:20542
SCIP_Bool SCIPisLT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
Definition: scip.c:41585
SCIP_ROW ** SCIPcolGetRows(SCIP_COL *col)
Definition: lp.c:18784
SCIP_Bool SCIProwIsModifiable(SCIP_ROW *row)
Definition: lp.c:19034
int SCIPgetNSepaRounds(SCIP *scip)
Definition: scip.c:37979
SCIP_Real SCIProwGetRhs(SCIP_ROW *row)
Definition: lp.c:18925
#define SCIPdebugPrintf
Definition: pub_message.h:80
static SCIP_DECL_SEPAEXECLP(sepaExeclpCmir)
Definition: sepa_cmir.c:1571
#define DEFAULT_MAXSEPACUTS
Definition: sepa_cmir.c:53
int SCIProwGetRank(SCIP_ROW *row)
Definition: lp.c:19004
SCIP_Real SCIPepsilon(SCIP *scip)
Definition: scip.c:41118
static SCIP_Bool varIsContinuous(SCIP_VAR *var)
Definition: sepa_cmir.c:637
SCIP_Bool SCIPisLE(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
Definition: scip.c:41598
SCIP_RETCODE SCIPaddPoolCut(SCIP *scip, SCIP_ROW *row)
Definition: scip.c:31062
SCIP_Bool SCIProwIsLocal(SCIP_ROW *row)
Definition: lp.c:19024
#define MAXFRAC
Definition: sepa_cmir.c:77
complemented mixed integer rounding cuts separator (Marchand&#39;s version)
SCIP_Real SCIPgetVectorEfficacyNorm(SCIP *scip, SCIP_Real *vals, int nvals)
Definition: scip.c:30891
SCIP_RETCODE SCIPgetLPRowsData(SCIP *scip, SCIP_ROW ***rows, int *nrows)
Definition: scip.c:26750
SCIP_RETCODE SCIPgetSolVals(SCIP *scip, SCIP_SOL *sol, int nvars, SCIP_VAR **vars, SCIP_Real *vals)
Definition: scip.c:35020
#define DEFAULT_DENSITYSCORE
Definition: sepa_cmir.c:57
SCIP_Real SCIPinfinity(SCIP *scip)
Definition: scip.c:41637
#define DEFAULT_AGGRTOL
Definition: sepa_cmir.c:66
int SCIPcolGetNLPNonz(SCIP_COL *col)
Definition: lp.c:18773
SCIP_RETCODE SCIPmakeRowIntegral(SCIP *scip, SCIP_ROW *row, SCIP_Real mindelta, SCIP_Real maxdelta, SCIP_Longint maxdnom, SCIP_Real maxscale, SCIP_Bool usecontvars, SCIP_Bool *success)
Definition: scip.c:28003
SCIP_RETCODE SCIPincludeSepaCmir(SCIP *scip)
Definition: sepa_cmir.c:1612
#define DEFAULT_MAXSEPACUTSROOT
Definition: sepa_cmir.c:54
SCIP_Longint SCIPgetNLPs(SCIP *scip)
Definition: scip.c:37435
const char * SCIProwGetName(SCIP_ROW *row)
Definition: lp.c:18974
SCIP_Bool SCIPisFeasGT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
Definition: scip.c:41946
SCIP_RETCODE SCIPcreateEmptyRowSepa(SCIP *scip, SCIP_ROW **row, SCIP_SEPA *sepa, const char *name, SCIP_Real lhs, SCIP_Real rhs, SCIP_Bool local, SCIP_Bool modifiable, SCIP_Bool removable)
Definition: scip.c:27629
SCIP_Bool SCIPisGT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
Definition: scip.c:41611
#define SEPA_NAME
Definition: sepa_cmir.c:31
SCIP_Real SCIPvarGetUbLocal(SCIP_VAR *var)
Definition: var.c:17123
public data structures and miscellaneous methods
void SCIPsepaSetData(SCIP_SEPA *sepa, SCIP_SEPADATA *sepadata)
Definition: sepa.c:554
void SCIProwChgRank(SCIP_ROW *row, int rank)
Definition: lp.c:19137
#define DEFAULT_MAXCONTSROOT
Definition: sepa_cmir.c:65
#define SCIP_Bool
Definition: def.h:53
#define DEFAULT_MAXTRIES
Definition: sepa_cmir.c:41
#define DEFAULT_DYNAMICCUTS
Definition: sepa_cmir.c:71
SCIP_Real SCIProwGetNorm(SCIP_ROW *row)
Definition: lp.c:18891
SCIP_RETCODE SCIPsetSepaCopy(SCIP *scip, SCIP_SEPA *sepa, SCIP_DECL_SEPACOPY((*sepacopy)))
Definition: scip.c:6702
static SCIP_RETCODE addCut(SCIP *scip, SCIP_SEPA *sepa, SCIP_SOL *sol, SCIP_Real *varsolvals, SCIP_Real *cutcoefs, SCIP_Real cutrhs, SCIP_Bool cutislocal, SCIP_Bool cutremovable, int cutrank, const char *cutclassname, SCIP_Bool *cutoff, int *ncuts)
Definition: sepa_cmir.c:176
#define MAX(x, y)
Definition: tclique_def.h:75
static SCIP_RETCODE aggregation(SCIP *scip, SCIP_SEPA *sepa, SCIP_SEPADATA *sepadata, SCIP_SOL *sol, SCIP_Real *varsolvals, SCIP_Real *bestcontlbs, SCIP_Real *bestcontubs, SCIP_Real *contvarscorebounds, SCIP_Real *rowlhsscores, SCIP_Real *rowrhsscores, int startrow, int maxaggrs, SCIP_Real maxslack, int maxconts, SCIP_Bool *wastried, SCIP_Bool *cutoff, int *ncuts)
Definition: sepa_cmir.c:693
#define DEFAULT_MAXSLACK
Definition: sepa_cmir.c:55
int SCIPgetDepth(SCIP *scip)
Definition: scip.c:38140
SCIP_RETCODE SCIPgetVarClosestVub(SCIP *scip, SCIP_VAR *var, SCIP_SOL *sol, SCIP_Real *closestvub, int *closestvubidx)
Definition: scip.c:21534
#define DEFAULT_MAXROUNDS
Definition: sepa_cmir.c:39
SCIP_Bool SCIPisGE(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
Definition: scip.c:41624
#define SCIP_REAL_MAX
Definition: def.h:128
SCIP_VARTYPE SCIPvarGetType(SCIP_VAR *var)
Definition: var.c:16608
#define SCIPallocBufferArray(scip, ptr, num)
Definition: scip.h:20585
SCIP_Real SCIPvarGetLbGlobal(SCIP_VAR *var)
Definition: var.c:17057
SCIP_Real SCIProwGetDualsol(SCIP_ROW *row)
Definition: lp.c:18935
#define DEFAULT_MAXROWFAC
Definition: sepa_cmir.c:62
#define REALABS(x)
Definition: def.h:151
#define DEFAULT_DENSITYOFFSET
Definition: sepa_cmir.c:61
SCIP_Real * SCIProwGetVals(SCIP_ROW *row)
Definition: lp.c:18871
int SCIPvarGetProbindex(SCIP_VAR *var)
Definition: var.c:16750
#define DEFAULT_MAXTRIESROOT
Definition: sepa_cmir.c:44
#define SCIP_Real
Definition: def.h:127
#define MIN(x, y)
Definition: memory.c:67
static SCIP_RETCODE storeCutInArrays(SCIP *scip, int nvars, SCIP_VAR **vars, SCIP_Real *cutcoefs, SCIP_Real *varsolvals, SCIP_VAR **cutvars, SCIP_Real *cutvals, int *cutlen, SCIP_Real *cutact)
Definition: sepa_cmir.c:129
SCIP_RETCODE SCIPprintRow(SCIP *scip, SCIP_ROW *row, FILE *file)
Definition: scip.c:28334
#define DEFAULT_MAXAGGRSROOT
Definition: sepa_cmir.c:52
#define BOUNDSWITCH
Definition: sepa_cmir.c:73
SCIP_RETCODE SCIPreleaseRow(SCIP *scip, SCIP_ROW **row)
Definition: scip.c:27738
#define SCIP_Longint
Definition: def.h:112
int SCIPsepaGetNCallsAtNode(SCIP_SEPA *sepa)
Definition: sepa.c:760
#define DEFAULT_MAXTESTDELTA
Definition: sepa_cmir.c:63
int SCIProwGetLPPos(SCIP_ROW *row)
Definition: lp.c:19104
static SCIP_DECL_SEPAFREE(sepaFreeCmir)
Definition: sepa_cmir.c:1553
#define SEPA_PRIORITY
Definition: sepa_cmir.c:33
int SCIProwGetNNonz(SCIP_ROW *row)
Definition: lp.c:18836
SCIP_RETCODE SCIPgetVarsData(SCIP *scip, SCIP_VAR ***vars, int *nvars, int *nbinvars, int *nintvars, int *nimplvars, int *ncontvars)
Definition: scip.c:10572
enum SCIP_Vartype SCIP_VARTYPE
Definition: type_var.h:58
#define SCIPfreeBufferArray(scip, ptr)
Definition: scip.h:20597
SCIP_Bool SCIPvarIsActive(SCIP_VAR *var)
Definition: var.c:16730
SCIP_RETCODE SCIPcutGenerationHeuristicCmir(SCIP *scip, SCIP_SEPA *sepa, SCIP_SOL *sol, SCIP_Real *varsolvals, int maxtestdelta, SCIP_Real *rowweights, SCIP_Real maxweight, int *weightinds, int nweightinds, int rowlensum, SCIP_Real boundswitch, SCIP_Bool usevbds, SCIP_Bool allowlocal, SCIP_Bool fixintegralrhs, int maxmksetcoefs, SCIP_Real maxweightrange, SCIP_Real minfrac, SCIP_Real maxfrac, SCIP_Bool trynegscaling, SCIP_Bool cutremovable, const char *cutclassname, SCIP_Bool *cutoff, int *ncuts, SCIP_Real *delta, SCIP_Bool *deltavalid)
Definition: sepa_cmir.c:429
#define SEPA_FREQ
Definition: sepa_cmir.c:34
#define SCIPdebug(x)
Definition: pub_message.h:74
#define MAKECONTINTEGRAL
Definition: sepa_cmir.c:78
static SCIP_RETCODE separateCuts(SCIP *scip, SCIP_SEPA *sepa, SCIP_SOL *sol, SCIP_RESULT *result)
Definition: sepa_cmir.c:1228
int SCIPgetNImplVars(SCIP *scip)
Definition: scip.c:10833
SCIP_RETCODE SCIPincludeSepaBasic(SCIP *scip, SCIP_SEPA **sepa, const char *name, const char *desc, int priority, int freq, SCIP_Real maxbounddist, SCIP_Bool usessubscip, SCIP_Bool delay, SCIP_DECL_SEPAEXECLP((*sepaexeclp)), SCIP_DECL_SEPAEXECSOL((*sepaexecsol)), SCIP_SEPADATA *sepadata)
Definition: scip.c:6660
#define DEFAULT_MAXROWDENSITY
Definition: sepa_cmir.c:60
SCIP_VAR * SCIPcolGetVar(SCIP_COL *col)
Definition: lp.c:18685
SCIP_Bool SCIPisPositive(SCIP *scip, SCIP_Real val)
Definition: scip.c:41697
SCIP_Real * SCIPcolGetVals(SCIP_COL *col)
Definition: lp.c:18794
SCIP_RETCODE SCIPaddRealParam(SCIP *scip, const char *name, const char *desc, SCIP_Real *valueptr, SCIP_Bool isadvanced, SCIP_Real defaultvalue, SCIP_Real minvalue, SCIP_Real maxvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip.c:3629
#define DEFAULT_MAXSLACKROOT
Definition: sepa_cmir.c:56
SCIP_Real SCIPsumepsilon(SCIP *scip)
Definition: scip.c:41132
SCIP_Real SCIPgetCutEfficacy(SCIP *scip, SCIP_SOL *sol, SCIP_ROW *cut)
Definition: scip.c:30836
#define SEPA_DESC
Definition: sepa_cmir.c:32
void SCIPsortedvecInsertInt(int *intarray, int keyval, int *len, int *pos)
#define SEPA_MAXBOUNDDIST
Definition: sepa_cmir.c:35
#define DEFAULT_MAXFAILSROOT
Definition: sepa_cmir.c:48
struct SCIP_SepaData SCIP_SEPADATA
Definition: type_sepa.h:38
#define SEPA_DELAY
Definition: sepa_cmir.c:37