Scippy

SCIP

Solving Constraint Integer Programs

heur_twoopt.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-2020 Konrad-Zuse-Zentrum */
7 /* fuer Informationstechnik Berlin */
8 /* */
9 /* SCIP is distributed under the terms of the ZIB Academic License. */
10 /* */
11 /* You should have received a copy of the ZIB Academic License */
12 /* along with SCIP; see the file COPYING. If not visit scipopt.org. */
13 /* */
14 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
15 
16 /**@file heur_twoopt.c
17  * @ingroup DEFPLUGINS_HEUR
18  * @brief primal heuristic to improve incumbent solution by flipping pairs of variables
19  * @author Timo Berthold
20  * @author Gregor Hendel
21  */
22 
23 /*---+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8----+----9----+----0----+----1----+----2*/
24 
25 #include "blockmemshell/memory.h"
26 #include "scip/heur_twoopt.h"
27 #include "scip/pub_heur.h"
28 #include "scip/pub_lp.h"
29 #include "scip/pub_message.h"
30 #include "scip/pub_misc.h"
31 #include "scip/pub_misc_sort.h"
32 #include "scip/pub_sol.h"
33 #include "scip/pub_var.h"
34 #include "scip/scip_heur.h"
35 #include "scip/scip_lp.h"
36 #include "scip/scip_mem.h"
37 #include "scip/scip_message.h"
38 #include "scip/scip_numerics.h"
39 #include "scip/scip_param.h"
40 #include "scip/scip_prob.h"
41 #include "scip/scip_randnumgen.h"
42 #include "scip/scip_sol.h"
43 #include "scip/scip_solvingstats.h"
44 #include <string.h>
45 
46 #define HEUR_NAME "twoopt"
47 #define HEUR_DESC "primal heuristic to improve incumbent solution by flipping pairs of variables"
48 #define HEUR_DISPCHAR SCIP_HEURDISPCHAR_ITERATIVE
49 #define HEUR_PRIORITY -20100
50 #define HEUR_FREQ -1
51 #define HEUR_FREQOFS 0
52 #define HEUR_MAXDEPTH -1
53 
54 #define HEUR_TIMING SCIP_HEURTIMING_AFTERNODE
55 #define HEUR_USESSUBSCIP FALSE /**< does the heuristic use a secondary SCIP instance? */
56 
57 /* default parameter values */
58 #define DEFAULT_INTOPT FALSE /**< optional integer optimization is applied by default */
59 #define DEFAULT_WAITINGNODES 0 /**< default number of nodes to wait after current best solution before calling heuristic */
60 #define DEFAULT_MATCHINGRATE 0.5 /**< default percentage by which two variables have to match in their LP-row set to be
61  * associated as pair by heuristic */
62 #define DEFAULT_MAXNSLAVES 199 /**< default number of slave candidates for a master variable */
63 #define DEFAULT_ARRAYSIZE 10 /**< the default array size for temporary arrays */
64 #define DEFAULT_RANDSEED 37 /**< initial random seed */
65 
66 /*
67  * Data structures
68  */
69 
70 /** primal heuristic data */
71 struct SCIP_HeurData
72 {
73  int lastsolindex; /**< index of last solution for which heuristic was performed */
74  SCIP_Real matchingrate; /**< percentage by which two variables have have to match in their LP-row
75  * set to be associated as pair by heuristic */
76  SCIP_VAR** binvars; /**< Array of binary variables which are sorted with respect to their occurrence
77  * in the LP-rows */
78  int nbinvars; /**< number of binary variables stored in heuristic array */
79  int waitingnodes; /**< user parameter to determine number of nodes to wait after last best solution
80  * before calling heuristic */
81  SCIP_Bool presolved; /**< flag to indicate whether presolving has already been executed */
82  int* binblockstart; /**< array to store the start indices of each binary block */
83  int* binblockend; /**< array to store the end indices of each binary block */
84  int nbinblocks; /**< number of blocks */
85 
86  /* integer variable twoopt data */
87  SCIP_Bool intopt; /**< parameter to determine if integer 2-opt should be applied */
88  SCIP_VAR** intvars; /**< array to store the integer variables in non-decreasing order
89  * with respect to their objective coefficient */
90  int nintvars; /**< the number of integer variables stored in array intvars */
91  int* intblockstart; /**< array to store the start indices of each binary block */
92  int* intblockend; /**< array to store the end indices of each binary block */
93  int nintblocks; /**< number of blocks */
94 
95  SCIP_Bool execute; /**< has presolveTwoOpt detected necessary structure for execution of heuristic? */
96  SCIP_RANDNUMGEN* randnumgen; /**< random number generator */
97  int maxnslaves; /**< delimits the maximum number of slave candidates for a master variable */
98 
99 #ifdef SCIP_STATISTIC
100  /* statistics */
101  int ntotalbinvars; /**< total number of binary variables over all runs */
102  int ntotalintvars; /**< total number of Integer variables over all runs */
103  int nruns; /**< counts the number of runs, i.e. the number of initialized
104  * branch and bound processes */
105  int maxbinblocksize; /**< maximum size of a binary block */
106  int maxintblocksize; /**< maximum size of an integer block */
107  int binnblockvars; /**< number of binary variables that appear in blocks */
108  int binnblocks; /**< number of blocks with at least two variables */
109  int intnblockvars; /**< number of Integer variables that appear in blocks */
110  int intnblocks; /**< number of blocks with at least two variables */
111  int binnexchanges; /**< number of executed changes of binary solution values leading to
112  * improvement in objective function */
113  int intnexchanges; /**< number of executed changes of Integer solution values leading to improvement in
114  * objective function */
115 #endif
116 };
117 
118 /** indicator for optimizing for binaries or integer variables */
119 enum Opttype
120 {
121  OPTTYPE_BINARY = 1,
123 };
124 typedef enum Opttype OPTTYPE;
126 /** indicator for direction of shifting variables */
127 enum Direction
128 {
129  DIRECTION_UP = 1,
132 };
133 typedef enum Direction DIRECTION;
135 /*
136  * Local methods
137  */
138 
139 /** Tries to switch the values of two binary or integer variables and checks feasibility with respect to the LP.
140  *
141  * @todo Adapt method not to copy entire activities array, but only the relevant region.
142  */
143 static
145  SCIP* scip, /**< scip instance */
146  SCIP_VAR* master, /**< first variable of variable pair */
147  SCIP_VAR* slave, /**< second variable of pair */
148  SCIP_Real mastersolval, /**< current value of variable1 in solution */
149  DIRECTION masterdir, /**< the direction into which the master variable has to be shifted */
150  SCIP_Real slavesolval, /**< current value of variable2 in solution */
151  DIRECTION slavedir, /**< the direction into which the slave variable has to be shifted */
152  SCIP_Real shiftval, /**< the value that variables should be shifted by */
153  SCIP_Real* activities, /**< the LP-row activities */
154  int nrows, /**< size of activities array */
155  SCIP_Bool* feasible /**< set to true if method has successfully switched the variable values */
156  )
157 { /*lint --e{715}*/
158  SCIP_COL* col;
159  SCIP_ROW** masterrows;
160  SCIP_ROW** slaverows;
161  SCIP_Real* mastercolvals;
162  SCIP_Real* slavecolvals;
163  int ncolmasterrows;
164  int ncolslaverows;
165  int i;
166  int j;
167 
168  assert(scip != NULL);
169  assert(master != NULL);
170  assert(slave != NULL);
171  assert(activities != NULL);
172  assert(SCIPisFeasGT(scip, shiftval, 0.0));
173 
174  assert(SCIPisFeasGE(scip, mastersolval + (int)masterdir * shiftval, SCIPvarGetLbGlobal(master)));
175  assert(SCIPisFeasLE(scip, mastersolval + (int)masterdir * shiftval, SCIPvarGetUbGlobal(master)));
176 
177  assert(SCIPisFeasGE(scip, slavesolval + (int)slavedir * shiftval, SCIPvarGetLbGlobal(slave)));
178  assert(SCIPisFeasLE(scip, slavesolval + (int)slavedir * shiftval, SCIPvarGetUbGlobal(slave)));
179 
180  /* get variable specific rows and coefficients for both master and slave. */
181  col = SCIPvarGetCol(master);
182  masterrows = SCIPcolGetRows(col);
183  mastercolvals = SCIPcolGetVals(col);
184  ncolmasterrows = SCIPcolGetNNonz(col);
185  assert(ncolmasterrows == 0 || masterrows != NULL);
186 
187  col = SCIPvarGetCol(slave);
188  slaverows = SCIPcolGetRows(col);
189  slavecolvals = SCIPcolGetVals(col);
190  ncolslaverows = SCIPcolGetNNonz(col);
191  assert(ncolslaverows == 0 || slaverows != NULL);
192 
193  /* update the activities of the LP rows of the master variable */
194  for( i = 0; i < ncolmasterrows && SCIProwGetLPPos(masterrows[i]) >= 0; ++i )
195  {
196  int rowpos;
197 
198  rowpos = SCIProwGetLPPos(masterrows[i]);
199  assert(rowpos < nrows);
200 
201  /* skip local rows */
202  if( rowpos >= 0 && ! SCIProwIsLocal(masterrows[i]) )
203  activities[rowpos] += mastercolvals[i] * (int)masterdir * shiftval;
204  }
205 
206  /* update the activities of the LP rows of the slave variable */
207  for( j = 0; j < ncolslaverows && SCIProwGetLPPos(slaverows[j]) >= 0; ++j )
208  {
209  int rowpos;
210 
211  rowpos = SCIProwGetLPPos(slaverows[j]);
212  assert(rowpos < nrows);
213 
214  /* skip local rows */
215  if( rowpos >= 0 && ! SCIProwIsLocal(slaverows[j]) )
216  {
217  activities[rowpos] += slavecolvals[j] * (int)slavedir * shiftval;
218  assert(SCIPisFeasGE(scip, activities[rowpos], SCIProwGetLhs(slaverows[j])));
219  assert(SCIPisFeasLE(scip, activities[rowpos], SCIProwGetRhs(slaverows[j])));
220  }
221  }
222 
223  /* in debug mode, the master rows are checked for feasibility which should be granted by the
224  * decision for a shift value */
225 #ifndef NDEBUG
226  for( i = 0; i < ncolmasterrows && SCIProwGetLPPos(masterrows[i]) >= 0; ++i )
227  {
228  /* local rows can be skipped */
229  if( SCIProwIsLocal(masterrows[i]) )
230  continue;
231 
232  assert(SCIPisFeasGE(scip, activities[SCIProwGetLPPos(masterrows[i])], SCIProwGetLhs(masterrows[i])));
233  assert(SCIPisFeasLE(scip, activities[SCIProwGetLPPos(masterrows[i])], SCIProwGetRhs(masterrows[i])));
234  }
235 #endif
236 
237  *feasible = TRUE;
238 
239  return SCIP_OKAY;
240 }
241 
242 /** Compare two variables with respect to their columns.
243  *
244  * Columns are treated as {0,1} vector, where every nonzero entry is treated as '1', and compared to each other
245  * lexicographically. I.e. var1 is < var2 if the corresponding column of var2 has the smaller single nonzero index of
246  * the two columns. This comparison costs O(constraints) in the worst case
247  */
248 static
249 int varColCompare(
250  SCIP_VAR* var1, /**< left argument of comparison */
251  SCIP_VAR* var2 /**< right argument of comparison */
252  )
253 {
254  SCIP_COL* col1;
255  SCIP_COL* col2;
256  SCIP_ROW** rows1;
257  SCIP_ROW** rows2;
258  int nnonzeros1;
259  int nnonzeros2;
260  int i;
261 
262  assert(var1 != NULL);
263  assert(var2 != NULL);
264 
265  /* get the necessary row and column data */
266  col1 = SCIPvarGetCol(var1);
267  col2 = SCIPvarGetCol(var2);
268  rows1 = SCIPcolGetRows(col1);
269  rows2 = SCIPcolGetRows(col2);
270  nnonzeros1 = SCIPcolGetNNonz(col1);
271  nnonzeros2 = SCIPcolGetNNonz(col2);
272 
273  assert(nnonzeros1 == 0 || rows1 != NULL);
274  assert(nnonzeros2 == 0 || rows2 != NULL);
275 
276  /* loop over the rows, stopped as soon as they differ in one index,
277  * or if counter reaches the end of a variables row set */
278  for( i = 0; i < nnonzeros1 && i < nnonzeros2; ++i )
279  {
280  if( SCIProwGetIndex(rows1[i]) != SCIProwGetIndex(rows2[i]) )
281  return SCIProwGetIndex(rows1[i]) - SCIProwGetIndex(rows2[i]);
282  }
283 
284  /* loop is finished, without differing in one of common row indices, due to loop invariant
285  * variable i reached either nnonzeros1 or nnonzeros2 or both.
286  * one can easily check that the difference of these two numbers always has the desired sign for comparison. */
287  return nnonzeros2 - nnonzeros1 ;
288 }
289 
290 /** implements a comparator to compare two variables with respect to their column entries */
291 static
292 SCIP_DECL_SORTPTRCOMP(SCIPvarcolComp)
293 {
294  return varColCompare((SCIP_VAR*) elem1, (SCIP_VAR*) elem2);
295 }
296 
297 /** checks if two given variables are contained in common LP rows,
298  * returns true if variables share the necessary percentage (matchingrate) of rows.
299  */
300 static
302  SCIP* scip, /**< current SCIP instance */
303  SCIP_VAR* var1, /**< first variable */
304  SCIP_VAR* var2, /**< second variable */
305  SCIP_Real matchingrate /**< determines the ratio of shared LP rows compared to the total number of
306  * LP-rows each variable appears in */
307  )
308 {
309  SCIP_COL* col1;
310  SCIP_COL* col2;
311  SCIP_ROW** rows1;
312  SCIP_ROW** rows2;
313  int nnonzeros1;
314  int nnonzeros2;
315  int i;
316  int j;
317  int nrows1not2; /* the number of LP-rows of variable 1 which variable 2 doesn't appear in */
318  int nrows2not1; /* vice versa */
319  int nrowmaximum;
320  int nrowabs;
321 
322  assert(var1 != NULL);
323  assert(var2 != NULL);
324 
325  /* get the necessary row and column data */
326  col1 = SCIPvarGetCol(var1);
327  col2 = SCIPvarGetCol(var2);
328  rows1 = SCIPcolGetRows(col1);
329  rows2 = SCIPcolGetRows(col2);
330  nnonzeros1 = SCIPcolGetNNonz(col1);
331  nnonzeros2 = SCIPcolGetNNonz(col2);
332 
333  assert(nnonzeros1 == 0 || rows1 != NULL);
334  assert(nnonzeros2 == 0 || rows2 != NULL);
335 
336  if( nnonzeros1 == 0 && nnonzeros2 == 0 )
337  return TRUE;
338 
339  /* initialize the counters for the number of rows not shared. */
340  nrowmaximum = MAX(nnonzeros1, nnonzeros2);
341 
342  nrowabs = ABS(nnonzeros1 - nnonzeros2);
343  nrows1not2 = nrowmaximum - nnonzeros2;
344  nrows2not1 = nrowmaximum - nnonzeros1;
345 
346  /* if the numbers of nonzero rows differs too much, w.r.t.matching ratio, the more expensive check over the rows
347  * doesn't have to be applied anymore because the counters for not shared rows can only increase.
348  */
349  assert(nrowmaximum > 0);
350 
351  if( (nrowmaximum - nrowabs) / (SCIP_Real) nrowmaximum < matchingrate )
352  return FALSE;
353 
354  i = 0;
355  j = 0;
356 
357  /* loop over all rows and determine number of non-shared rows */
358  while( i < nnonzeros1 && j < nnonzeros2 )
359  {
360  /* variables share a common row */
361  if( SCIProwGetIndex(rows1[i]) == SCIProwGetIndex(rows2[j]) )
362  {
363  ++i;
364  ++j;
365  }
366  /* variable 1 appears in rows1[i], variable 2 doesn't */
367  else if( SCIProwGetIndex(rows1[i]) < SCIProwGetIndex(rows2[j]) )
368  {
369  ++i;
370  ++nrows1not2;
371  }
372  /* variable 2 appears in rows2[j], variable 1 doesn't */
373  else
374  {
375  ++j;
376  ++nrows2not1;
377  }
378  }
379 
380  /* now apply the ratio based comparison, that is if the ratio of shared rows is greater or equal the matching rate
381  * for each variable */
382  return ( SCIPisFeasLE(scip, matchingrate, (nnonzeros1 - nrows1not2) / (SCIP_Real)(nnonzeros1)) ||
383  SCIPisFeasLE(scip, matchingrate, (nnonzeros2 - nrows2not1) / (SCIP_Real)(nnonzeros2)) ); /*lint !e795 */
384 }
385 
386 /** Determines a bound by which the absolute solution value of two integer variables can be shifted at most.
387  *
388  * The criterion is the maintenance of feasibility of any global LP row.
389  * The first implementation only considers shifting proportion 1:1, i.e. if master value is shifted by a certain
390  * integer value k downwards, the value of slave is simultaneously shifted by k upwards.
391  */
392 static
394  SCIP* scip, /**< current scip instance */
395  SCIP_SOL* sol, /**< current incumbent */
396  SCIP_VAR* master, /**< current master variable */
397  DIRECTION masterdirection, /**< the shifting direction of the master variable */
398  SCIP_VAR* slave, /**< slave variable with same LP_row set as master variable */
399  DIRECTION slavedirection, /**< the shifting direction of the slave variable */
400  SCIP_Real* activities, /**< array of LP row activities */
401  int nrows /**< the number of rows in LP and the size of the activities array */
402  )
403 { /*lint --e{715}*/
404  SCIP_Real masterbound;
405  SCIP_Real slavebound;
407 
408  SCIP_COL* col;
409  SCIP_ROW** slaverows;
410  SCIP_ROW** masterrows;
411  SCIP_Real* mastercolvals;
412  SCIP_Real* slavecolvals;
413  int nslaverows;
414  int nmasterrows;
415  int i;
416  int j;
417 
418  assert(scip != NULL);
419  assert(sol != NULL);
420  assert(master != NULL);
421  assert(slave != NULL);
422  assert(SCIPvarIsIntegral(master) && SCIPvarIsIntegral(slave));
423  assert(masterdirection == DIRECTION_UP || masterdirection == DIRECTION_DOWN);
424  assert(slavedirection == DIRECTION_UP || slavedirection == DIRECTION_DOWN);
425 
426  /* determine the trivial variable bounds for shift */
427  if( masterdirection == DIRECTION_UP )
428  masterbound = SCIPvarGetUbGlobal(master) - SCIPgetSolVal(scip, sol, master);
429  else
430  masterbound = SCIPgetSolVal(scip, sol, master) - SCIPvarGetLbGlobal(master);
431 
432  if( slavedirection == DIRECTION_UP )
433  slavebound = SCIPvarGetUbGlobal(slave) - SCIPgetSolVal(scip, sol, slave);
434  else
435  slavebound = SCIPgetSolVal(scip, sol, slave) - SCIPvarGetLbGlobal(slave);
436 
437  bound = MIN(slavebound, masterbound);
438  assert(!SCIPisInfinity(scip,bound));
439 
440  if( bound < 0.5 )
441  return 0.0;
442 
443  /* get the necessary row and and column data for each variable */
444  col = SCIPvarGetCol(slave);
445  slaverows = SCIPcolGetRows(col);
446  slavecolvals = SCIPcolGetVals(col);
447  nslaverows = SCIPcolGetNNonz(col);
448 
449  col = SCIPvarGetCol(master);
450  mastercolvals = SCIPcolGetVals(col);
451  masterrows = SCIPcolGetRows(col);
452  nmasterrows = SCIPcolGetNNonz(col);
453 
454  assert(nslaverows == 0 || slavecolvals != NULL);
455  assert(nmasterrows == 0 || mastercolvals != NULL);
456 
457  SCIPdebugMsg(scip, " Master: %s with direction %d and %d rows, Slave: %s with direction %d and %d rows \n", SCIPvarGetName(master),
458  (int)masterdirection, nmasterrows, SCIPvarGetName(slave), (int)slavedirection, nslaverows);
459 
460  /* loop over all LP rows and determine the maximum integer bound by which both variables
461  * can be shifted without loss of feasibility
462  */
463  i = 0;
464  j = 0;
465  while( (i < nslaverows || j < nmasterrows) && SCIPisPositive(scip, bound) )
466  {
467  SCIP_ROW* row;
468  SCIP_Real effect;
469  SCIP_Real rhs;
470  SCIP_Real lhs;
471  SCIP_Real activity;
472  int rowpos;
473  int masterindex;
474  int slaveindex;
475  SCIP_Bool slaveincrement;
476  SCIP_Bool masterincrement;
477 
478  /* check if one pointer already reached the end of the respective array */
479  if( i < nslaverows && SCIProwGetLPPos(slaverows[i]) == -1 )
480  {
481  SCIPdebugMsg(scip, " Slaverow %s is not in LP (i=%d, j=%d)\n", SCIProwGetName(slaverows[i]), i, j);
482  i = nslaverows;
483  continue;
484  }
485  if( j < nmasterrows && SCIProwGetLPPos(masterrows[j]) == -1 )
486  {
487  SCIPdebugMsg(scip, " Masterrow %s is not in LP (i=%d, j=%d) \n", SCIProwGetName(masterrows[j]), i, j);
488  j = nmasterrows;
489  continue;
490  }
491 
492  slaveincrement = FALSE;
493  /* If one counter has already reached its limit, assign a huge number to the corresponding
494  * row index to simulate an always greater row position. */
495  if( i < nslaverows )
496  slaveindex = SCIProwGetIndex(slaverows[i]);
497  else
498  slaveindex = INT_MAX;
499 
500  if( j < nmasterrows )
501  masterindex = SCIProwGetIndex(masterrows[j]);
502  else
503  masterindex = INT_MAX;
504 
505  assert(0 <= slaveindex && 0 <= masterindex);
506 
507  assert(slaveindex < INT_MAX || masterindex < INT_MAX);
508 
509  /* the current row is the one with the smaller index */
510  if( slaveindex <= masterindex )
511  {
512  rowpos = SCIProwGetLPPos(slaverows[i]);
513  row = slaverows[i];
514  slaveincrement = TRUE;
515  masterincrement = (slaveindex == masterindex);
516  }
517  else
518  {
519  assert(j < nmasterrows);
520 
521  rowpos = SCIProwGetLPPos(masterrows[j]);
522  row = masterrows[j];
523  masterincrement = TRUE;
524  }
525  assert(row != NULL);
526 
527  /* local rows can be skipped */
528  if( !SCIProwIsLocal(row) )
529  {
530  /* effect is the effect on the row activity by shifting the variables by 1 in the respective directions */
531  effect = 0.0;
532  if( slaveindex <= masterindex )
533  effect += (slavecolvals[i] * (int)slavedirection);
534  if( masterindex <= slaveindex )
535  effect += (mastercolvals[j] * (int)masterdirection);
536 
537  /* get information about the current row */
538  if( rowpos >= 0 && !SCIPisFeasZero(scip, effect) )
539  {
540  /* effect does not equal zero, the bound is determined as minimum positive integer such that
541  * feasibility of this constraint is maintained.
542  * if constraint is an equality constraint, activity and lhs/rhs should be feasibly equal, which
543  * will cause the method to return zero.
544  */
545  assert(rowpos < nrows);
546 
547  activity = activities[rowpos];
548  rhs = SCIProwGetRhs(row);
549  lhs = SCIProwGetLhs(row);
550 
551  /* if the row is an equation, abort because of effect being nonzero */
552  if( SCIPisFeasEQ(scip, lhs, rhs) )
553  return 0.0;
554 
555  assert(SCIPisFeasLE(scip, lhs, activity) && SCIPisFeasLE(scip, activity, rhs));
556 
557  SCIPdebugMsg(scip, " %g <= %g <= %g, bound = %g, effect = %g (%g * %d + %g * %d) (i=%d,j=%d)\n", lhs, activity, rhs, bound, effect,
558  slaveindex <= masterindex ? slavecolvals[i] : 0.0, (int)slavedirection, masterindex <= slaveindex ? mastercolvals[j] : 0.0,
559  (int)masterdirection, i, j);
560 
561  /* if the row has a left hand side, ensure that shifting preserves feasibility of this ">="-constraint */
562  if( !SCIPisInfinity(scip, -lhs) && SCIPisFeasLT(scip, activity + (effect * bound), lhs) )
563  {
564  SCIP_Real newval;
565 
566  assert(SCIPisNegative(scip, effect));
567 
568  newval = SCIPfeasFloor(scip, (lhs - activity)/effect); /*lint !e414*/
569  bound = MIN(bound - 1.0, newval);
570  }
571 
572  /* if the row has an upper bound, ensure that shifting preserves feasibility of this "<="-constraint */
573  if( !SCIPisInfinity(scip, rhs) && SCIPisFeasGT(scip, activity + (effect * bound), rhs) )
574  {
575  SCIP_Real newval;
576 
577  assert(SCIPisPositive(scip, effect));
578 
579  newval = SCIPfeasFloor(scip, (rhs - activity)/effect); /*lint !e414*/
580  bound = MIN(bound - 1.0, newval);
581  }
582 
583  assert(SCIPisFeasLE(scip, lhs, activity + effect * bound) && SCIPisFeasGE(scip, rhs, activity + effect * bound));
584  assert(SCIPisFeasIntegral(scip, bound));
585  }
586  else
587  {
588  SCIPdebugMsg(scip, " Zero effect on row %s, effect %g, master coeff: %g slave coeff: %g (i=%d, j=%d)\n",
589  SCIProwGetName(row), effect, mastercolvals[j], slavecolvals[i], i, j);
590  }
591  }
592  else
593  {
594  SCIPdebugMsg(scip, " Row %s is local.\n", SCIProwGetName(row));
595  }
596 
597  /* increase the counters which belong to the corresponding row. Both counters are increased by
598  * 1 iff rowpos1 <= rowpos2 <= rowpos1 */
599  if( slaveincrement )
600  ++i;
601  if( masterincrement )
602  ++j;
603  }
604 
605  /* due to numerical reasons, bound can be negative. A variable shift by a negative bound is not desired by
606  * by the heuristic -> Change the return value to zero */
607  if( !SCIPisPositive(scip, bound) )
608  bound = 0.0;
609 
610  return bound;
611 }
612 
613 /** Disposes variable with no heuristic relevancy, e.g., due to a fixed solution value, from its neighborhood block.
614  *
615  * The affected neighborhood block is reduced by 1.
616  */
617 static
618 void disposeVariable(
619  SCIP_VAR** vars, /**< problem variables */
620  int* blockend, /**< contains end index of block */
621  int varindex /**< variable index */
622  )
623 {
624  assert(blockend != NULL);
625  assert(varindex <= *blockend);
626 
627  vars[varindex] = vars[*blockend];
628  --(*blockend);
629 }
630 
631 /** realizes the presolve independently from type of variables it's applied to */
632 static
634  SCIP* scip, /**< current scip */
635  SCIP_VAR** vars, /**< problem vars */
636  SCIP_VAR*** varspointer, /**< pointer to heuristic specific variable memory */
637  int nvars, /**< the number of variables */
638  int* nblocks, /**< pointer to store the number of detected blocks */
639  int* maxblocksize, /**< maximum size of a block */
640  int* nblockvars, /**< pointer to store the number of block variables */
641  int** blockstart, /**< pointer to store the array of block start indices */
642  int** blockend, /**< pointer to store the array of block end indices */
643  SCIP_HEUR* heur, /**< the heuristic */
644  SCIP_HEURDATA* heurdata /**< the heuristic data */
645  )
646 {
647  int v;
648  int startindex;
649 
650  assert(scip != NULL);
651  assert(vars != NULL);
652  assert(nvars >= 2);
653  assert(nblocks != NULL);
654  assert(nblockvars != NULL);
655  assert(blockstart != NULL);
656  assert(blockend != NULL);
657  assert(heur != NULL);
658  assert(heurdata != NULL);
659 
660  /* allocate the heuristic specific variables */
661  SCIP_CALL( SCIPduplicateBlockMemoryArray(scip, varspointer, vars, nvars));
662 
663  /* sort the variables with respect to their columns */
664  SCIPsortPtr((void**)(*varspointer), SCIPvarcolComp, nvars);
665 
666  /* start determining blocks, i.e. a set of at least two variables which share most of their row set.
667  * If there is none, heuristic does not need to be executed.
668  */
669  startindex = 0;
670  *nblocks = 0;
671  *nblockvars = 0;
672 
673  SCIP_CALL( SCIPallocBlockMemoryArray(scip, blockstart, nvars/2) );
674  SCIP_CALL( SCIPallocBlockMemoryArray(scip, blockend, nvars/2) );
675 
676  /* loop over variables and compare neighbors */
677  for( v = 1; v < nvars; ++v )
678  {
679  if( !checkConstraintMatching(scip, (*varspointer)[startindex], (*varspointer)[v], heurdata->matchingrate) )
680  {
681  /* current block has its last variable at position v-1. If v differs from startindex by at least 2,
682  * a block is detected. Update the data correspondingly */
683  if( v - startindex >= 2 )
684  {
685  assert(*nblocks < nvars/2);
686  (*nblockvars) += v - startindex;
687  (*maxblocksize) = MAX((*maxblocksize), v - startindex);
688  (*blockstart)[*nblocks] = startindex;
689  (*blockend)[*nblocks] = v - 1;
690  (*nblocks)++;
691  }
692  startindex = v;
693  }
694  else if( v == nvars - 1 && v - startindex >= 1 )
695  {
696  assert(*nblocks < nvars/2);
697  (*nblockvars) += v - startindex + 1;
698  (*maxblocksize) = MAX((*maxblocksize), v - startindex + 1);
699  (*blockstart)[*nblocks] = startindex;
700  (*blockend)[*nblocks] = v;
701  (*nblocks)++;
702  }
703  }
704 
705  /* reallocate memory with respect to the number of found blocks; if there were none, free the memory */
706  if( *nblocks > 0 )
707  {
708  SCIP_CALL( SCIPreallocBlockMemoryArray(scip, blockstart, nvars/2, *nblocks) );
709  SCIP_CALL( SCIPreallocBlockMemoryArray(scip, blockend, nvars/2, *nblocks) );
710  }
711  else
712  {
713  SCIPfreeBlockMemoryArray(scip, blockstart, nvars/2);
714  SCIPfreeBlockMemoryArray(scip, blockend, nvars/2);
715 
716  *blockstart = NULL;
717  *blockend = NULL;
718  }
719 
720  return SCIP_OKAY;
721 }
722 
723 /** initializes the required structures for execution of heuristic.
724  *
725  * If objective coefficient functions are not all equal, each Binary and Integer variables are sorted
726  * into heuristic-specific arrays with respect to their lexicographical column order,
727  * where every zero in a column is interpreted as zero and every nonzero as '1'.
728  * After the sorting, the variables are compared with respect to user parameter matchingrate and
729  * the heuristic specific blocks are determined.
730  */
731 static
733  SCIP* scip, /**< current scip instance */
734  SCIP_HEUR* heur, /**< heuristic */
735  SCIP_HEURDATA* heurdata /**< the heuristic data */
736  )
737 {
738  int nbinvars;
739  int nintvars;
740  int nvars;
741  SCIP_VAR** vars;
742  int nbinblockvars = 0;
743  int nintblockvars;
744  int maxbinblocksize = 0;
745  int maxintblocksize;
746 
747  assert(scip != NULL);
748  assert(heurdata != NULL);
749 
750  /* ensure that method is not executed if presolving was already applied once in current branch and bound process */
751  if( heurdata->presolved )
752  return SCIP_OKAY;
753 
754  /* get necessary variable information, i.e. number of binary and integer variables */
755  SCIP_CALL( SCIPgetVarsData(scip, &vars, &nvars, &nbinvars, &nintvars, NULL, NULL) );
756 
757  /* if number of binary problem variables exceeds 2, they are subject to 2-optimization algorithm, hence heuristic
758  * calls innerPresolve method to detect necessary structures. */
759  if( nbinvars >= 2 )
760  {
761  SCIP_CALL( innerPresolve(scip, vars, &(heurdata->binvars), nbinvars, &(heurdata->nbinblocks), &maxbinblocksize,
762  &nbinblockvars, &(heurdata->binblockstart), &(heurdata->binblockend), heur, heurdata) );
763  }
764 
765  heurdata->nbinvars = nbinvars;
766  heurdata->execute = nbinvars > 1 && heurdata->nbinblocks > 0;
767 
768 #ifdef SCIP_STATISTIC
769  /* update statistics */
770  heurdata->binnblocks += (heurdata->nbinblocks);
771  heurdata->binnblockvars += nbinblockvars;
772  heurdata->ntotalbinvars += nbinvars;
773  heurdata->maxbinblocksize = MAX(maxbinblocksize, heurdata->maxbinblocksize);
774 
775  SCIPstatisticMessage(" Twoopt BINARY presolving finished with <%d> blocks, <%d> block variables \n",
776  heurdata->nbinblocks, nbinblockvars);
777 #endif
778 
779  if( heurdata->intopt && nintvars > 1 )
780  {
781  SCIP_CALL( innerPresolve(scip, &(vars[nbinvars]), &(heurdata->intvars), nintvars, &(heurdata->nintblocks), &maxintblocksize,
782  &nintblockvars, &(heurdata->intblockstart), &(heurdata->intblockend),
783  heur, heurdata) );
784 
785  heurdata->execute = heurdata->execute || heurdata->nintblocks > 0;
786 
787 #ifdef SCIP_STATISTIC
788  /* update statistics */
789  heurdata->intnblocks += heurdata->nintblocks;
790  heurdata->intnblockvars += nintblockvars;
791  heurdata->ntotalintvars += nintvars;
792  heurdata->maxintblocksize = MAX(maxintblocksize, heurdata->maxintblocksize);
793  SCIPstatisticMessage(" Twoopt Integer presolving finished with <%d> blocks, <%d> block variables \n",
794  heurdata->nintblocks, nintblockvars);
795  SCIPstatisticMessage(" INTEGER coefficients are all equal \n");
796 #endif
797  }
798  heurdata->nintvars = nintvars;
799 
800  /* presolving is finished, heuristic data is updated*/
801  heurdata->presolved = TRUE;
802  SCIPheurSetData(heur, heurdata);
803 
804  return SCIP_OKAY;
805 }
806 
807 /*
808  * Callback methods of primal heuristic
809  */
810 
811 /** copy method for primal heuristic plugins (called when SCIP copies plugins) */
812 static
813 SCIP_DECL_HEURCOPY(heurCopyTwoopt)
814 { /*lint --e{715}*/
815  assert(scip != NULL);
816  assert(heur != NULL);
817  assert(strcmp(SCIPheurGetName(heur), HEUR_NAME) == 0);
818 
819  /* call inclusion method of primal heuristic */
821 
822  return SCIP_OKAY;
823 }
824 
825 /** destructor of primal heuristic to free user data (called when SCIP is exiting) */
826 static
827 SCIP_DECL_HEURFREE(heurFreeTwoopt)
828 { /*lint --e{715}*/
829  SCIP_HEURDATA* heurdata;
830 
831  assert(heur != NULL);
832  assert(strcmp(SCIPheurGetName(heur), HEUR_NAME) == 0);
833  assert(scip != NULL);
834 
835  /* free heuristic data */
836  heurdata = SCIPheurGetData(heur);
837  assert(heurdata != NULL);
838 
839  SCIPfreeBlockMemory(scip, &heurdata);
840  SCIPheurSetData(heur, NULL);
841 
842  return SCIP_OKAY;
843 }
844 
845 /** initialization method of primal heuristic (called after problem was transformed) */
846 static
847 SCIP_DECL_HEURINIT(heurInitTwoopt)
848 {
849  SCIP_HEURDATA* heurdata;
850  assert(heur != NULL);
851  assert(strcmp(SCIPheurGetName(heur), HEUR_NAME) == 0);
852  assert(scip != NULL);
853 
854  heurdata = SCIPheurGetData(heur);
855  assert(heurdata != NULL);
856 
857  /* heuristic has not run yet, all heuristic specific data is set to initial values */
858  heurdata->nbinvars = 0;
859  heurdata->nintvars = 0;
860  heurdata->lastsolindex = -1;
861  heurdata->presolved = FALSE;
862  heurdata->nbinblocks = 0;
863  heurdata->nintblocks = 0;
864 
865  /* create random number generator */
866  SCIP_CALL( SCIPcreateRandom(scip, &heurdata->randnumgen,
868 
869 #ifdef SCIP_STATISTIC
870  /* initialize statistics */
871  heurdata->binnexchanges = 0;
872  heurdata->intnexchanges = 0;
873  heurdata->binnblockvars = 0;
874  heurdata->intnblockvars = 0;
875  heurdata->binnblocks = 0;
876  heurdata->intnblocks = 0;
877 
878  heurdata->maxbinblocksize = 0;
879  heurdata->maxintblocksize = 0;
880 
881  heurdata->ntotalbinvars = 0;
882  heurdata->ntotalintvars = 0;
883  heurdata->nruns = 0;
884 #endif
885 
886  /* all pointers are initially set to NULL. Since presolving
887  * of the heuristic requires a lot of calculation time on some instances,
888  * but might not be needed e.g. if problem is infeasible, presolving is applied
889  * when heuristic is executed for the first time
890  */
891  heurdata->binvars = NULL;
892  heurdata->intvars = NULL;
893  heurdata->binblockstart = NULL;
894  heurdata->binblockend = NULL;
895  heurdata->intblockstart = NULL;
896  heurdata->intblockend = NULL;
897 
898  SCIPheurSetData(heur, heurdata);
899 
900  return SCIP_OKAY;
901 }
902 
903 /* Realizes the 2-optimization algorithm, which tries to improve incumbent solution
904  * by shifting pairs of variables which share a common row set.
905  */
906 static
908  SCIP* scip, /**< current SCIP instance */
909  SCIP_SOL* worksol, /**< working solution */
910  SCIP_VAR** vars, /**< binary or integer variables */
911  int* blockstart, /**< contains start indices of blocks */
912  int* blockend, /**< contains end indices of blocks */
913  int nblocks, /**< the number of blocks */
914  OPTTYPE opttype, /**< are binaries or integers optimized */
915  SCIP_Real* activities, /**< the LP-row activities */
916  int nrows, /**< the number of LP rows */
917  SCIP_Bool* improvement, /**< was there a successful shift? */
918  SCIP_Bool* varboundserr, /**< has the current incumbent already been cut off */
919  SCIP_HEURDATA* heurdata /**< the heuristic data */
920  )
921 { /*lint --e{715}*/
922  int b;
923  SCIP_Real* objchanges;
924  SCIP_VAR** bestmasters;
925  SCIP_VAR** bestslaves;
926  int* bestdirections;
927  int arraysize;
928  int npairs = 0;
929 
930  assert(scip != NULL);
931  assert(nblocks > 0);
932  assert(blockstart != NULL && blockend != NULL);
933  assert(varboundserr != NULL);
934  assert(activities != NULL);
935  assert(worksol != NULL);
936  assert(improvement != NULL);
937 
938  *varboundserr = FALSE;
939 
940  SCIP_CALL( SCIPallocBufferArray(scip, &bestmasters, DEFAULT_ARRAYSIZE) );
941  SCIP_CALL( SCIPallocBufferArray(scip, &bestslaves, DEFAULT_ARRAYSIZE) );
942  SCIP_CALL( SCIPallocBufferArray(scip, &objchanges, DEFAULT_ARRAYSIZE) );
943  SCIP_CALL( SCIPallocBufferArray(scip, &bestdirections, DEFAULT_ARRAYSIZE) );
944  arraysize = DEFAULT_ARRAYSIZE;
945 
946  /* iterate over blocks */
947  for( b = 0; b < nblocks; ++b )
948  {
949  int m;
950  int blocklen;
951 
952  blocklen = blockend[b] - blockstart[b] + 1;
953 
954  /* iterate over variables in current block */
955  for( m = 0; m < blocklen; ++m )
956  {
957  /* determine the new master variable for heuristic's optimization method */
958  SCIP_VAR* master;
959  SCIP_Real masterobj;
960  SCIP_Real mastersolval;
961  SCIP_Real bestimprovement;
962  SCIP_Real bestbound;
963  int bestslavepos;
964  int s;
965  int firstslave;
966  int nslaves;
967  int bestdirection;
968  DIRECTION bestmasterdir;
969  DIRECTION bestslavedir;
970 
971  master = vars[blockstart[b] + m]; /*lint !e679*/
972  masterobj = SCIPvarGetObj(master);
973  mastersolval = SCIPgetSolVal(scip, worksol, master);
974 
975  /* due to cuts or fixings of solution values, worksol might not be feasible w.r.t. its bounds.
976  * Exit method in that case. */
977  if( SCIPisFeasGT(scip, mastersolval, SCIPvarGetUbGlobal(master)) || SCIPisFeasLT(scip, mastersolval, SCIPvarGetLbGlobal(master)) )
978  {
979  *varboundserr = TRUE;
980  SCIPdebugMsg(scip, "Solution has violated variable bounds for var %s: %g <= %g <= %g \n",
981  SCIPvarGetName(master), SCIPvarGetLbGlobal(master), mastersolval, SCIPvarGetUbGlobal(master));
982  goto TERMINATE;
983  }
984 
985  /* if variable has fixed solution value, it is deleted from heuristic array */
986  if( SCIPisFeasEQ(scip, SCIPvarGetUbGlobal(master), SCIPvarGetLbGlobal(master)) )
987  {
988  disposeVariable(vars, &(blockend[b]), blockstart[b] + m);
989  --blocklen;
990  continue;
991  }
992  else if( SCIPvarGetStatus(master) != SCIP_VARSTATUS_COLUMN )
993  continue;
994 
995  assert(SCIPisFeasIntegral(scip, mastersolval));
996 
997  assert(opttype == OPTTYPE_INTEGER || (SCIPisFeasLE(scip, mastersolval, 1.0) || SCIPisFeasGE(scip, mastersolval, 0.0)));
998 
999  /* initialize the data of the best available shift */
1000  bestimprovement = 0.0;
1001  bestslavepos = -1;
1002  bestbound = 0.0;
1003  bestmasterdir = DIRECTION_NONE;
1004  bestslavedir = DIRECTION_NONE;
1005  bestdirection = -1;
1006 
1007  /* in blocks with more than heurdata->maxnslaves variables, a slave candidate region is chosen */
1008  if( heurdata->maxnslaves >= 0 && blocklen > heurdata->maxnslaves )
1009  firstslave = SCIPrandomGetInt(heurdata->randnumgen, blockstart[b] + m, blockend[b]);
1010  else
1011  firstslave = blockstart[b] + m + 1;
1012 
1013  nslaves = MIN((heurdata->maxnslaves == -1 ? INT_MAX : heurdata->maxnslaves), blocklen);
1014 
1015  /* Loop over block and determine a slave shift candidate for master variable.
1016  * If more than one candidate is available, choose the shift which improves objective function
1017  * the most. */
1018  for( s = 0; s < nslaves; ++s )
1019  {
1020  SCIP_VAR* slave;
1021  SCIP_Real slaveobj;
1022  SCIP_Real slavesolval;
1023  SCIP_Real changedobj;
1024  SCIP_Real diffdirbound;
1025  SCIP_Real equaldirbound;
1026  int directions;
1027  int slaveindex;
1028 
1029  slaveindex = (firstslave + s - blockstart[b]) % blocklen;
1030  slaveindex += blockstart[b];
1031 
1032  /* in case of a small block, we do not want to try possible pairings twice */
1033  if( (blocklen <= heurdata->maxnslaves || heurdata->maxnslaves == -1) && slaveindex < blockstart[b] + m )
1034  break;
1035  /* master and slave should not be the same variable */
1036  if( slaveindex == blockstart[b] + m )
1037  continue;
1038 
1039  /* get the next slave variable */
1040  slave = vars[slaveindex];
1041  slaveobj = SCIPvarGetObj(slave);
1042  slavesolval = SCIPgetSolVal(scip, worksol, slave);
1043  changedobj = 0.0;
1044 
1045  assert(SCIPvarGetType(master) == SCIPvarGetType(slave));
1046  assert(SCIPisFeasIntegral(scip, slavesolval));
1047  assert(opttype == OPTTYPE_INTEGER || (SCIPisFeasLE(scip, mastersolval, 1.0) || SCIPisFeasGE(scip, mastersolval, 0.0)));
1048 
1049  /* solution is not feasible w.r.t. the variable bounds, stop optimization in this case */
1050  if( SCIPisFeasGT(scip, slavesolval, SCIPvarGetUbGlobal(slave)) || SCIPisFeasLT(scip, slavesolval, SCIPvarGetLbGlobal(slave)) )
1051  {
1052  *varboundserr = TRUE;
1053  SCIPdebugMsg(scip, "Solution has violated variable bounds for var %s: %g <= %g <= %g \n",
1054  SCIPvarGetName(slave), SCIPvarGetLbGlobal(slave), slavesolval, SCIPvarGetUbGlobal(slave));
1055  goto TERMINATE;
1056  }
1057 
1058  /* if solution value of the variable is fixed, delete it from the remaining candidates in the block */
1059  if( SCIPisFeasEQ(scip, SCIPvarGetUbGlobal(slave), SCIPvarGetLbGlobal(slave) ) )
1060  {
1061  disposeVariable(vars, &(blockend[b]), slaveindex);
1062  --blocklen;
1063  continue;
1064  }
1065  else if( SCIPvarGetStatus(master) != SCIP_VARSTATUS_COLUMN )
1066  continue;
1067 
1068  /* determine the shifting direction to improve the objective function */
1069  /* assert(SCIPisFeasGT(scip, masterobj, slaveobj)); */
1070 
1071  /* The heuristic chooses the shifting direction and the corresponding maximum nonnegative
1072  * integer shift value for the two variables which preserves feasibility and improves
1073  * the objective function value. */
1074  directions = -1;
1075  diffdirbound = 0.0;
1076  equaldirbound = 0.0;
1077 
1078  if( SCIPisFeasLT(scip, masterobj - slaveobj, 0.0) )
1079  {
1080  diffdirbound = determineBound(scip, worksol, master, DIRECTION_UP, slave, DIRECTION_DOWN, activities, nrows);
1081  directions = 2;
1082  /* the improvement of objective function is calculated */
1083  changedobj = (masterobj - slaveobj) * diffdirbound;
1084  }
1085  else if( SCIPisFeasGT(scip, masterobj - slaveobj, 0.0) )
1086  {
1087  diffdirbound = determineBound(scip, worksol, master, DIRECTION_DOWN, slave, DIRECTION_UP, activities, nrows);
1088  directions = 1;
1089  changedobj = (slaveobj - masterobj) * diffdirbound;
1090  }
1091 
1092  if( SCIPisFeasLT(scip, masterobj + slaveobj, 0.0) )
1093  {
1094  equaldirbound = determineBound(scip, worksol, master, DIRECTION_UP, slave, DIRECTION_UP, activities, nrows);
1095  if( SCIPisFeasLT(scip, (slaveobj + masterobj) * equaldirbound, changedobj) )
1096  {
1097  changedobj = (slaveobj + masterobj) * equaldirbound;
1098  directions = 3;
1099  }
1100  }
1101  else if( SCIPisFeasGT(scip, masterobj + slaveobj, 0.0) )
1102  {
1103  equaldirbound = determineBound(scip, worksol, master, DIRECTION_DOWN, slave, DIRECTION_DOWN, activities, nrows);
1104  if( SCIPisFeasLT(scip, -(slaveobj + masterobj) * equaldirbound, changedobj) )
1105  {
1106  changedobj = -(slaveobj + masterobj) * equaldirbound;
1107  directions = 0;
1108  }
1109  }
1110  assert(SCIPisFeasIntegral(scip, equaldirbound));
1111  assert(SCIPisFeasIntegral(scip, diffdirbound));
1112  assert(SCIPisFeasGE(scip, equaldirbound, 0.0));
1113  assert(SCIPisFeasGE(scip, diffdirbound, 0.0));
1114 
1115  /* choose the candidate which improves the objective function the most */
1116  if( (SCIPisFeasGT(scip, equaldirbound, 0.0) || SCIPisFeasGT(scip, diffdirbound, 0.0))
1117  && SCIPisFeasLT(scip, changedobj, bestimprovement) )
1118  {
1119  bestimprovement = changedobj;
1120  bestslavepos = slaveindex;
1121  bestdirection = directions;
1122 
1123  /* the most promising shift, i.e., the one which can improve the objective
1124  * the most, is recorded by the integer 'directions'. It is recovered via the use
1125  * of a binary representation of the four different combinations for the shifting directions
1126  * of two variables */
1127  if( directions / 2 == 1 )
1128  bestmasterdir = DIRECTION_UP;
1129  else
1130  bestmasterdir = DIRECTION_DOWN;
1131 
1132  if( directions % 2 == 1 )
1133  bestslavedir = DIRECTION_UP;
1134  else
1135  bestslavedir = DIRECTION_DOWN;
1136 
1137  if( bestmasterdir == bestslavedir )
1138  bestbound = equaldirbound;
1139  else
1140  bestbound = diffdirbound;
1141  }
1142  }
1143 
1144  /* choose the most promising candidate, if one exists */
1145  if( bestslavepos >= 0 )
1146  {
1147  if( npairs == arraysize )
1148  {
1149  SCIP_CALL( SCIPreallocBufferArray(scip, &bestmasters, 2 * arraysize) );
1150  SCIP_CALL( SCIPreallocBufferArray(scip, &bestslaves, 2 * arraysize) );
1151  SCIP_CALL( SCIPreallocBufferArray(scip, &objchanges, 2 * arraysize) );
1152  SCIP_CALL( SCIPreallocBufferArray(scip, &bestdirections, 2 * arraysize) );
1153  arraysize = 2 * arraysize;
1154  }
1155  assert( npairs < arraysize );
1156 
1157  bestmasters[npairs] = master;
1158  bestslaves[npairs] = vars[bestslavepos];
1159  objchanges[npairs] = ((int)bestslavedir * SCIPvarGetObj(bestslaves[npairs]) + (int)bestmasterdir * masterobj) * bestbound;
1160  bestdirections[npairs] = bestdirection;
1161 
1162  assert(objchanges[npairs] < 0);
1163 
1164  SCIPdebugMsg(scip, " Saved candidate pair {%s=%g, %s=%g} with objectives <%g>, <%g> to be set to {%g, %g} %d\n",
1165  SCIPvarGetName(master), mastersolval, SCIPvarGetName(bestslaves[npairs]), SCIPgetSolVal(scip, worksol, bestslaves[npairs]) ,
1166  masterobj, SCIPvarGetObj(bestslaves[npairs]), mastersolval + (int)bestmasterdir * bestbound, SCIPgetSolVal(scip, worksol, bestslaves[npairs])
1167  + (int)bestslavedir * bestbound, bestdirections[npairs]);
1168 
1169  ++npairs;
1170  }
1171  }
1172  }
1173 
1174  if( npairs == 0 )
1175  goto TERMINATE;
1176 
1177  SCIPsortRealPtrPtrInt(objchanges, (void**)bestmasters, (void**)bestslaves, bestdirections, npairs);
1178 
1179  for( b = 0; b < npairs; ++b )
1180  {
1181  SCIP_VAR* master;
1182  SCIP_VAR* slave;
1183  SCIP_Real mastersolval;
1184  SCIP_Real slavesolval;
1185  SCIP_Real masterobj;
1186  SCIP_Real slaveobj;
1187  SCIP_Real bound;
1188  DIRECTION masterdir;
1189  DIRECTION slavedir;
1190 
1191  master = bestmasters[b];
1192  slave = bestslaves[b];
1193  mastersolval = SCIPgetSolVal(scip, worksol, master);
1194  slavesolval = SCIPgetSolVal(scip, worksol, slave);
1195  masterobj =SCIPvarGetObj(master);
1196  slaveobj = SCIPvarGetObj(slave);
1197 
1198  assert(0 <= bestdirections[b] && bestdirections[b] < 4);
1199 
1200  if( bestdirections[b] / 2 == 1 )
1201  masterdir = DIRECTION_UP;
1202  else
1203  masterdir = DIRECTION_DOWN;
1204 
1205  if( bestdirections[b] % 2 == 1 )
1206  slavedir = DIRECTION_UP;
1207  else
1208  slavedir = DIRECTION_DOWN;
1209 
1210  bound = determineBound(scip, worksol, master, masterdir, slave, slavedir, activities, nrows);
1211 
1212  if( !SCIPisZero(scip, bound) )
1213  {
1214  SCIP_Bool feasible;
1215 #ifndef NDEBUG
1216  SCIP_Real changedobj;
1217 #endif
1218 
1219  SCIPdebugMsg(scip, " Promising candidates {%s=%g, %s=%g} with objectives <%g>, <%g> to be set to {%g, %g}\n",
1220  SCIPvarGetName(master), mastersolval, SCIPvarGetName(slave), slavesolval,
1221  masterobj, slaveobj, mastersolval + (int)masterdir * bound, slavesolval + (int)slavedir * bound);
1222 
1223 #ifndef NDEBUG
1224  /* the improvement of objective function is calculated */
1225  changedobj = ((int)slavedir * slaveobj + (int)masterdir * masterobj) * bound;
1226  assert(SCIPisFeasLT(scip, changedobj, 0.0));
1227 #endif
1228 
1230  /* try to change the solution values of the variables */
1231  feasible = FALSE;
1232  SCIP_CALL( shiftValues(scip, master, slave, mastersolval, masterdir, slavesolval, slavedir, bound,
1233  activities, nrows, &feasible) );
1234 
1235  if( feasible )
1236  {
1237  /* The variables' solution values were successfully shifted and can hence be updated. */
1238  assert(SCIPisFeasIntegral(scip, mastersolval + ((int)masterdir * bound)));
1239  assert(SCIPisFeasIntegral(scip, slavesolval + ((int)slavedir * bound)));
1240 
1241  SCIP_CALL( SCIPsetSolVal(scip, worksol, master, mastersolval + (int)masterdir * bound) );
1242  SCIP_CALL( SCIPsetSolVal(scip, worksol, slave, slavesolval + (int)slavedir * bound) );
1243  SCIPdebugMsg(scip, " Feasible shift: <%s>[%g, %g] (obj: %f) <%f> --> <%f>\n",
1244  SCIPvarGetName(master), SCIPvarGetLbGlobal(master), SCIPvarGetUbGlobal(master), masterobj, mastersolval, SCIPgetSolVal(scip, worksol, master));
1245  SCIPdebugMsg(scip, " <%s>[%g, %g] (obj: %f) <%f> --> <%f>\n",
1246  SCIPvarGetName(slave), SCIPvarGetLbGlobal(slave), SCIPvarGetUbGlobal(slave), slaveobj, slavesolval, SCIPgetSolVal(scip, worksol, slave));
1247 
1248 #ifdef SCIP_STATISTIC
1249  /* update statistics */
1250  if( opttype == OPTTYPE_BINARY )
1251  ++(heurdata->binnexchanges);
1252  else
1253  ++(heurdata->intnexchanges);
1254 #endif
1255 
1256  *improvement = TRUE;
1257  }
1258  }
1259  }
1260  TERMINATE:
1261  SCIPfreeBufferArray(scip, &bestdirections);
1262  SCIPfreeBufferArray(scip, &objchanges);
1263  SCIPfreeBufferArray(scip, &bestslaves);
1264  SCIPfreeBufferArray(scip, &bestmasters);
1265 
1266  return SCIP_OKAY;
1267 }
1268 
1269 /** deinitialization method of primal heuristic (called before transformed problem is freed) */
1270 static
1271 SCIP_DECL_HEUREXIT(heurExitTwoopt)
1273  SCIP_HEURDATA* heurdata;
1274 
1275  heurdata = SCIPheurGetData(heur);
1276  assert(heurdata != NULL);
1277 
1278  /*ensure that initialization was successful */
1279  assert(heurdata->nbinvars <= 1 || heurdata->binvars != NULL);
1280 
1281 #ifdef SCIP_STATISTIC
1282  /* print relevant statistics to console */
1284  " Twoopt Binary Statistics : "
1285  "%6.2g %6.2g %4.2g %4.0g %6d (blocks/run, variables/run, varpercentage, avg. block size, max block size) \n",
1286  heurdata->nruns == 0 ? 0.0 : (SCIP_Real)heurdata->binnblocks/(heurdata->nruns),
1287  heurdata->nruns == 0 ? 0.0 : (SCIP_Real)heurdata->binnblockvars/(heurdata->nruns),
1288  heurdata->ntotalbinvars == 0 ? 0.0 : (SCIP_Real)heurdata->binnblockvars/(heurdata->ntotalbinvars) * 100.0,
1289  heurdata->binnblocks == 0 ? 0.0 : heurdata->binnblockvars/(SCIP_Real)(heurdata->binnblocks),
1290  heurdata->maxbinblocksize);
1291 
1293  " Twoopt Integer statistics : "
1294  "%6.2g %6.2g %4.2g %4.0g %6d (blocks/run, variables/run, varpercentage, avg block size, max block size) \n",
1295  heurdata->nruns == 0 ? 0.0 : (SCIP_Real)heurdata->intnblocks/(heurdata->nruns),
1296  heurdata->nruns == 0 ? 0.0 : (SCIP_Real)heurdata->intnblockvars/(heurdata->nruns),
1297  heurdata->ntotalintvars == 0 ? 0.0 : (SCIP_Real)heurdata->intnblockvars/(heurdata->ntotalintvars) * 100.0,
1298  heurdata->intnblocks == 0 ? 0.0 : heurdata->intnblockvars/(SCIP_Real)(heurdata->intnblocks),
1299  heurdata->maxintblocksize);
1300 
1302  " Twoopt results : "
1303  "%6d %6d %4d %4.2g (runs, binary exchanges, Integer shiftings, matching rate)\n",
1304  heurdata->nruns,
1305  heurdata->binnexchanges,
1306  heurdata->intnexchanges,
1307  heurdata->matchingrate);
1308 
1309  /* set statistics to initial values*/
1310  heurdata->binnblockvars = 0;
1311  heurdata->binnblocks = 0;
1312  heurdata->intnblocks = 0;
1313  heurdata->intnblockvars = 0;
1314  heurdata->binnexchanges = 0;
1315  heurdata->intnexchanges = 0;
1316 #endif
1317 
1318  /* free the allocated memory for the binary variables */
1319  if( heurdata->binvars != NULL )
1320  {
1321  SCIPfreeBlockMemoryArray(scip, &heurdata->binvars, heurdata->nbinvars);
1322  }
1323 
1324  if( heurdata->nbinblocks > 0 )
1325  {
1326  assert(heurdata->binblockstart != NULL);
1327  assert(heurdata->binblockend != NULL);
1328 
1329  SCIPfreeBlockMemoryArray(scip, &heurdata->binblockstart, heurdata->nbinblocks);
1330  SCIPfreeBlockMemoryArray(scip, &heurdata->binblockend, heurdata->nbinblocks);
1331  }
1332  heurdata->nbinvars = 0;
1333  heurdata->nbinblocks = 0;
1334 
1335  if( heurdata->nintblocks > 0 )
1336  {
1337  assert(heurdata->intblockstart != NULL);
1338  assert(heurdata->intblockend != NULL);
1339 
1340  SCIPfreeBlockMemoryArray(scip, &heurdata->intblockstart, heurdata->nintblocks);
1341  SCIPfreeBlockMemoryArray(scip, &heurdata->intblockend, heurdata->nintblocks);
1342  }
1343 
1344  /* free the allocated memory for the integers */
1345  if( heurdata->intvars != NULL )
1346  {
1347  SCIPfreeBlockMemoryArray(scip, &heurdata->intvars, heurdata->nintvars);
1348  }
1349 
1350  heurdata->nbinblocks = 0;
1351  heurdata->nintblocks = 0;
1352  heurdata->nbinvars = 0;
1353  heurdata->nintvars = 0;
1354 
1355  assert(heurdata->binvars == NULL);
1356  assert(heurdata->intvars == NULL);
1357 
1358  /* free random number generator */
1359  SCIPfreeRandom(scip, &heurdata->randnumgen);
1360 
1361  SCIPheurSetData(heur, heurdata);
1362 
1363  return SCIP_OKAY;
1364 }
1365 
1366 /** solving process initialization method of primal heuristic (called when branch and bound process is about to begin) */
1367 static
1368 SCIP_DECL_HEURINITSOL(heurInitsolTwoopt)
1370  SCIP_HEURDATA* heurdata;
1371  assert(heur != NULL);
1372  assert(strcmp(SCIPheurGetName(heur), HEUR_NAME) == 0);
1373  assert(scip != NULL);
1374 
1375  /* get heuristic data */
1376  heurdata = SCIPheurGetData(heur);
1377 
1378  assert(heurdata != NULL);
1379  assert(heurdata->binvars == NULL && heurdata->intvars == NULL);
1380  assert(heurdata->binblockstart == NULL && heurdata->binblockend == NULL);
1381  assert(heurdata->intblockstart == NULL && heurdata->intblockend == NULL);
1382 
1383  /* set heuristic data to initial values, but increase the total number of runs */
1384  heurdata->nbinvars = 0;
1385  heurdata->nintvars = 0;
1386  heurdata->lastsolindex = -1;
1387  heurdata->presolved = FALSE;
1388 
1389 #ifdef SCIP_STATISTIC
1390  ++(heurdata->nruns);
1391 #endif
1392 
1393  SCIPheurSetData(heur, heurdata);
1394 
1395  return SCIP_OKAY;
1396 }
1397 
1398 
1399 /** solving process deinitialization method of primal heuristic (called before branch and bound process data is freed) */
1400 static
1401 SCIP_DECL_HEUREXITSOL(heurExitsolTwoopt)
1403  SCIP_HEURDATA* heurdata;
1404  int nbinvars;
1405  int nintvars;
1406 
1407  assert(heur != NULL);
1408  assert(scip != NULL);
1409  assert(strcmp(SCIPheurGetName(heur), HEUR_NAME) == 0);
1410  assert(scip != NULL);
1411 
1412  /* get heuristic data */
1413  heurdata = SCIPheurGetData(heur);
1414 
1415  assert(heurdata != NULL);
1416 
1417  nbinvars = heurdata->nbinvars;
1418  nintvars = heurdata->nintvars;
1419 
1420  /* free the allocated memory for the binary variables */
1421  if( heurdata->binvars != NULL )
1422  {
1423  SCIPfreeBlockMemoryArray(scip, &heurdata->binvars, nbinvars);
1424  }
1425  if( heurdata->binblockstart != NULL )
1426  {
1427  assert(heurdata->binblockend != NULL);
1428 
1429  SCIPfreeBlockMemoryArray(scip, &heurdata->binblockstart, heurdata->nbinblocks);
1430  SCIPfreeBlockMemoryArray(scip, &heurdata->binblockend, heurdata->nbinblocks);
1431  }
1432  heurdata->nbinvars = 0;
1433  heurdata->nbinblocks = 0;
1434 
1435  if( heurdata->intblockstart != NULL )
1436  {
1437  assert(heurdata->intblockend != NULL);
1438 
1439  SCIPfreeBlockMemoryArray(scip, &heurdata->intblockstart, heurdata->nintblocks);
1440  SCIPfreeBlockMemoryArray(scip, &heurdata->intblockend, heurdata->nintblocks);
1441  }
1442  heurdata->nintblocks = 0;
1443 
1444  /* free the allocated memory for the integers */
1445  if( heurdata->intvars != NULL )
1446  {
1447  SCIPfreeBlockMemoryArray(scip, &heurdata->intvars, nintvars);
1448  }
1449 
1450  heurdata->nintvars = 0;
1451 
1452  assert(heurdata->binvars == NULL && heurdata->intvars == NULL);
1453  assert(heurdata->binblockstart == NULL && heurdata->binblockend == NULL);
1454  assert(heurdata->intblockstart == NULL && heurdata->intblockend == NULL);
1455 
1456  /* set heuristic data */
1457  SCIPheurSetData(heur, heurdata);
1458 
1459  return SCIP_OKAY;
1460 }
1461 
1462 /** execution method of primal heuristic */
1463 static
1464 SCIP_DECL_HEUREXEC(heurExecTwoopt)
1465 { /*lint --e{715}*/
1466  SCIP_HEURDATA* heurdata;
1467  SCIP_SOL* bestsol;
1468  SCIP_SOL* worksol;
1469  SCIP_ROW** lprows;
1470  SCIP_Real* activities;
1471  SCIP_COL** cols;
1472  int ncols;
1473  int nbinvars;
1474  int nintvars;
1475  int ndiscvars;
1476  int nlprows;
1477  int i;
1478  int ncolsforsorting;
1479  SCIP_Bool improvement;
1480  SCIP_Bool presolthiscall;
1481  SCIP_Bool varboundserr;
1482 
1483  assert(heur != NULL);
1484  assert(scip != NULL);
1485  assert(result != NULL);
1486 
1487  /* get heuristic data */
1488  heurdata = SCIPheurGetData(heur);
1489  assert(heurdata != NULL);
1490 
1491  *result = SCIP_DIDNOTRUN;
1492 
1493  /* we need an LP */
1494  if( SCIPgetNLPRows(scip) == 0 )
1495  return SCIP_OKAY;
1496 
1497  bestsol = SCIPgetBestSol(scip);
1498 
1499  /* ensure that heuristic has not already been processed on current incumbent */
1500  if( bestsol == NULL || heurdata->lastsolindex == SCIPsolGetIndex(bestsol) )
1501  return SCIP_OKAY;
1502 
1503  heurdata->lastsolindex = SCIPsolGetIndex(bestsol);
1504 
1505  /* we can only work on solutions valid in the transformed space */
1506  if( SCIPsolIsOriginal(bestsol) )
1507  return SCIP_OKAY;
1508 
1509 #ifdef SCIP_DEBUG
1510  SCIP_CALL( SCIPprintSol(scip, bestsol, NULL, TRUE) );
1511 #endif
1512 
1513  /* ensure that the user defined number of nodes after last best solution has been reached, return otherwise */
1514  if( (SCIPgetNNodes(scip) - SCIPsolGetNodenum(bestsol)) < heurdata->waitingnodes )
1515  return SCIP_OKAY;
1516 
1517  presolthiscall = FALSE;
1518  SCIP_CALL( SCIPgetLPColsData(scip,&cols, &ncols) );
1519  ndiscvars = SCIPgetNBinVars(scip) + SCIPgetNIntVars(scip);
1520  ncolsforsorting = MIN(ncols, ndiscvars);
1521 
1522  /* ensure that heuristic specific presolve is applied when heuristic is executed first */
1523  if( !heurdata->presolved )
1524  {
1525  SCIP_CALL( SCIPgetLPColsData(scip,&cols, &ncols) );
1526 
1527  for( i = 0; i < ncolsforsorting; ++i )
1528  SCIPcolSort(cols[i]);
1529 
1530  SCIP_CALL( presolveTwoOpt(scip, heur, heurdata) );
1531  presolthiscall = TRUE;
1532  }
1533 
1534  assert(heurdata->presolved);
1535 
1536  SCIPdebugMsg(scip, " Twoopt heuristic is %sexecuting.\n", heurdata->execute ? "" : "not ");
1537  /* ensure that presolve has detected structures in the problem to which the 2-optimization can be applied.
1538  * That is if variables exist which share a common set of LP-rows. */
1539  if( !heurdata->execute )
1540  return SCIP_OKAY;
1541 
1542  nbinvars = heurdata->nbinvars;
1543  nintvars = heurdata->nintvars;
1544  ndiscvars = nbinvars + nintvars;
1545 
1546  /* we need to be able to start diving from current node in order to resolve the LP
1547  * with continuous or implicit integer variables
1548  */
1549  if( SCIPgetNVars(scip) > ndiscvars && ( !SCIPhasCurrentNodeLP(scip) || SCIPgetLPSolstat(scip) != SCIP_LPSOLSTAT_OPTIMAL ) )
1550  return SCIP_OKAY;
1551 
1552  /* problem satisfies all necessary conditions for 2-optimization heuristic, execute heuristic! */
1553  *result = SCIP_DIDNOTFIND;
1554 
1555  /* initialize a working solution as a copy of the current incumbent to be able to store
1556  * possible improvements obtained by 2-optimization */
1557  SCIP_CALL( SCIPcreateSolCopy(scip, &worksol, bestsol) );
1558  SCIPsolSetHeur(worksol, heur);
1559 
1560  /* get the LP row activities from current incumbent bestsol */
1561  SCIP_CALL( SCIPgetLPRowsData(scip, &lprows, &nlprows) );
1562  SCIP_CALL( SCIPallocBufferArray(scip, &activities, nlprows) );
1563 
1564  for( i = 0; i < nlprows; i++ )
1565  {
1566  SCIP_ROW* row;
1567 
1568  row = lprows[i];
1569  assert(row != NULL);
1570  assert(SCIProwGetLPPos(row) == i);
1571  SCIPdebugMsg(scip, " Row <%d> is %sin LP: \n", i, SCIProwGetLPPos(row) >= 0 ? "" : "not ");
1572  SCIPdebug( SCIP_CALL( SCIPprintRow(scip, row, NULL) ) );
1573  activities[i] = SCIPgetRowSolActivity(scip, row, bestsol);
1574 
1575  /* Heuristic does not provide infeasibility recovery, thus if any constraint is violated,
1576  * execution has to be terminated.
1577  */
1578  if( !SCIProwIsLocal(row) && (SCIPisFeasLT(scip, activities[i], SCIProwGetLhs(row))
1579  || SCIPisFeasGT(scip, activities[i], SCIProwGetRhs(row))) )
1580  goto TERMINATE;
1581  }
1582 
1583  if( !presolthiscall )
1584  {
1585  for( i = 0; i < ncolsforsorting; ++i )
1586  SCIPcolSort(cols[i]);
1587  }
1588  SCIPdebugMsg(scip, " Twoopt heuristic has initialized activities and sorted rows! \n");
1589 
1590  /* start with binary optimization */
1591  improvement = FALSE;
1592  varboundserr = FALSE;
1593 
1594  if( heurdata->nbinblocks > 0 )
1595  {
1596  SCIP_CALL( optimize(scip, worksol, heurdata->binvars, heurdata->binblockstart, heurdata->binblockend, heurdata->nbinblocks,
1597  OPTTYPE_BINARY, activities, nlprows, &improvement, &varboundserr, heurdata) );
1598 
1599  SCIPdebugMsg(scip, " Binary Optimization finished!\n");
1600  }
1601 
1602  if( varboundserr )
1603  goto TERMINATE;
1604 
1605  /* ensure that their are at least two integer variables which do not have the same coefficient
1606  * in the objective function. In one of these cases, the heuristic will automatically skip the
1607  * integer variable optimization */
1608  if( heurdata->nintblocks > 0 )
1609  {
1610  assert(heurdata->intopt);
1611  SCIP_CALL( optimize(scip, worksol, heurdata->intvars, heurdata->intblockstart, heurdata->intblockend, heurdata->nintblocks,
1612  OPTTYPE_INTEGER, activities, nlprows, &improvement, &varboundserr, heurdata) );
1613 
1614  SCIPdebugMsg(scip, " Integer Optimization finished!\n");
1615  }
1616 
1617  if( ! improvement || varboundserr )
1618  goto TERMINATE;
1619 
1620  if( SCIPgetNVars(scip) == ndiscvars )
1621  {
1622  /* the problem is a pure IP, hence, no continuous or implicit variables are left for diving.
1623  * try if new working solution is feasible in original problem */
1624  SCIP_Bool success;
1625 #ifndef NDEBUG
1626  SCIP_CALL( SCIPtrySol(scip, worksol, FALSE, FALSE, TRUE, TRUE, TRUE, &success) );
1627 #else
1628  SCIP_CALL( SCIPtrySol(scip, worksol, FALSE, FALSE, FALSE, FALSE, TRUE, &success) );
1629 #endif
1630 
1631  if( success )
1632  {
1633  SCIPdebugMsg(scip, "found feasible shifted solution:\n");
1634  SCIPdebug( SCIP_CALL( SCIPprintSol(scip, worksol, NULL, FALSE) ) );
1635  heurdata->lastsolindex = SCIPsolGetIndex(bestsol);
1636  *result = SCIP_FOUNDSOL;
1637 
1638 #ifdef SCIP_STATISTIC
1639  SCIPstatisticMessage("***Twoopt improved solution found by %10s . \n",
1640  SCIPsolGetHeur(bestsol) != NULL ? SCIPheurGetName(SCIPsolGetHeur(bestsol)) :"Tree");
1641 #endif
1642  }
1643  }
1644  /* fix the integer variables and start diving to optimize continuous variables with respect to reduced domain */
1645  else
1646  {
1647  SCIP_VAR** allvars;
1648  SCIP_Bool lperror;
1649 #ifdef NDEBUG
1650  SCIP_RETCODE retstat;
1651 #endif
1652 
1653  SCIPdebugMsg(scip, "shifted solution should be feasible -> solve LP to fix continuous variables to best values\n");
1654 
1655  allvars = SCIPgetVars(scip);
1656 
1657 #ifdef SCIP_DEBUG
1658  for( i = ndiscvars; i < SCIPgetNVars(scip); ++i )
1659  {
1660  SCIPdebugMsg(scip, " Cont. variable <%s>, status %d with bounds [%g <= %g <= x <= %g <= %g]\n",
1661  SCIPvarGetName(allvars[i]), SCIPvarGetStatus(allvars[i]), SCIPvarGetLbGlobal(allvars[i]), SCIPvarGetLbLocal(allvars[i]), SCIPvarGetUbLocal(allvars[i]),
1662  SCIPvarGetUbGlobal(allvars[i]));
1663  }
1664 #endif
1665 
1666  /* start diving to calculate the LP relaxation */
1667  SCIP_CALL( SCIPstartDive(scip) );
1668 
1669  /* set the bounds of the variables: fixed for integers, global bounds for continuous */
1670  for( i = 0; i < SCIPgetNVars(scip); ++i )
1671  {
1672  if( SCIPvarGetStatus(allvars[i]) == SCIP_VARSTATUS_COLUMN )
1673  {
1674  SCIP_CALL( SCIPchgVarLbDive(scip, allvars[i], SCIPvarGetLbGlobal(allvars[i])) );
1675  SCIP_CALL( SCIPchgVarUbDive(scip, allvars[i], SCIPvarGetUbGlobal(allvars[i])) );
1676  }
1677  }
1678 
1679  /* apply this after global bounds to not cause an error with intermediate empty domains */
1680  for( i = 0; i < ndiscvars; ++i )
1681  {
1682  if( SCIPvarGetStatus(allvars[i]) == SCIP_VARSTATUS_COLUMN )
1683  {
1684  SCIP_Real solval;
1685 
1686  solval = SCIPgetSolVal(scip, worksol, allvars[i]);
1687 
1688  assert(SCIPvarGetType(allvars[i]) != SCIP_VARTYPE_CONTINUOUS && SCIPisFeasIntegral(scip, solval));
1689 
1690  SCIP_CALL( SCIPchgVarLbDive(scip, allvars[i], solval) );
1691  SCIP_CALL( SCIPchgVarUbDive(scip, allvars[i], solval) );
1692  }
1693  }
1694  for( i = 0; i < ndiscvars; ++i )
1695  {
1696  assert( SCIPisFeasEQ(scip, SCIPgetVarLbDive(scip, allvars[i]), SCIPgetVarUbDive(scip, allvars[i])) );
1697  }
1698  /* solve LP */
1699  SCIPdebugMsg(scip, " -> old LP iterations: %" SCIP_LONGINT_FORMAT "\n", SCIPgetNLPIterations(scip));
1700 
1701  /* Errors in the LP solver should not kill the overall solving process, if the LP is just needed for a heuristic.
1702  * Hence in optimized mode, the return code is caught and a warning is printed, only in debug mode, SCIP will stop. */
1703 #ifdef NDEBUG
1704  retstat = SCIPsolveDiveLP(scip, -1, &lperror, NULL);
1705  if( retstat != SCIP_OKAY )
1706  {
1707  SCIPwarningMessage(scip, "Error while solving LP in Twoopt heuristic; LP solve terminated with code <%d>\n",retstat);
1708  }
1709 #else
1710  SCIP_CALL( SCIPsolveDiveLP(scip, -1, &lperror, NULL) );
1711 #endif
1712 
1713  SCIPdebugMsg(scip, " -> new LP iterations: %" SCIP_LONGINT_FORMAT "\n", SCIPgetNLPIterations(scip));
1714  SCIPdebugMsg(scip, " -> error=%u, status=%d\n", lperror, SCIPgetLPSolstat(scip));
1715 
1716  /* check if this is a feasible solution */
1717  if( !lperror && SCIPgetLPSolstat(scip) == SCIP_LPSOLSTAT_OPTIMAL )
1718  {
1719  SCIP_Bool success;
1720 
1721  /* copy the current LP solution to the working solution */
1722  SCIP_CALL( SCIPlinkLPSol(scip, worksol) );
1723 
1724  /* check solution for feasibility */
1725 #ifndef NDEBUG
1726  SCIP_CALL( SCIPtrySol(scip, worksol, FALSE, FALSE, TRUE, TRUE, TRUE, &success) );
1727 #else
1728  SCIP_CALL( SCIPtrySol(scip, worksol, FALSE, FALSE, FALSE, FALSE, TRUE, &success) );
1729 #endif
1730 
1731  if( success )
1732  {
1733  SCIPdebugMsg(scip, "found feasible shifted solution:\n");
1734  SCIPdebug( SCIP_CALL( SCIPprintSol(scip, worksol, NULL, FALSE) ) );
1735  heurdata->lastsolindex = SCIPsolGetIndex(bestsol);
1736  *result = SCIP_FOUNDSOL;
1737 
1738 #ifdef SCIP_STATISTIC
1739  SCIPstatisticMessage("*** Twoopt improved solution found by %10s . \n",
1740  SCIPsolGetHeur(bestsol) != NULL ? SCIPheurGetName(SCIPsolGetHeur(bestsol)) :"Tree");
1741 #endif
1742  }
1743  }
1744 
1745  /* terminate the diving */
1746  SCIP_CALL( SCIPendDive(scip) );
1747  }
1748 
1749  TERMINATE:
1750  SCIPdebugMsg(scip, "Termination of Twoopt heuristic\n");
1751  SCIPfreeBufferArray(scip, &activities);
1752  SCIP_CALL( SCIPfreeSol(scip, &worksol) );
1753 
1754  return SCIP_OKAY;
1755 }
1756 
1757 /*
1758  * primal heuristic specific interface methods
1759  */
1760 
1761 /** creates the twoopt primal heuristic and includes it in SCIP */
1763  SCIP* scip /**< SCIP data structure */
1764  )
1765 {
1766  SCIP_HEURDATA* heurdata;
1767  SCIP_HEUR* heur;
1768 
1769  /* create Twoopt primal heuristic data */
1770  SCIP_CALL( SCIPallocBlockMemory(scip, &heurdata) );
1771 
1772  /* include primal heuristic */
1773  SCIP_CALL( SCIPincludeHeurBasic(scip, &heur,
1775  HEUR_MAXDEPTH, HEUR_TIMING, HEUR_USESSUBSCIP, heurExecTwoopt, heurdata) );
1776 
1777  assert(heur != NULL);
1778 
1779  /* set non-NULL pointers to callback methods */
1780  SCIP_CALL( SCIPsetHeurCopy(scip, heur, heurCopyTwoopt) );
1781  SCIP_CALL( SCIPsetHeurFree(scip, heur, heurFreeTwoopt) );
1782  SCIP_CALL( SCIPsetHeurInit(scip, heur, heurInitTwoopt) );
1783  SCIP_CALL( SCIPsetHeurExit(scip, heur, heurExitTwoopt) );
1784  SCIP_CALL( SCIPsetHeurInitsol(scip, heur, heurInitsolTwoopt) );
1785  SCIP_CALL( SCIPsetHeurExitsol(scip, heur, heurExitsolTwoopt) );
1786 
1787  /* include boolean flag intopt */
1788  SCIP_CALL( SCIPaddBoolParam(scip, "heuristics/twoopt/intopt", " Should Integer-2-Optimization be applied or not?",
1789  &heurdata->intopt, TRUE, DEFAULT_INTOPT, NULL, NULL) );
1790 
1791  /* include parameter waitingnodes */
1792  SCIP_CALL( SCIPaddIntParam(scip, "heuristics/twoopt/waitingnodes", "user parameter to determine number of "
1793  "nodes to wait after last best solution before calling heuristic",
1794  &heurdata->waitingnodes, TRUE, DEFAULT_WAITINGNODES, 0, 10000, NULL, NULL));
1795 
1796  /* include parameter maxnslaves */
1797  SCIP_CALL( SCIPaddIntParam(scip, "heuristics/twoopt/maxnslaves", "maximum number of slaves for one master variable",
1798  &heurdata->maxnslaves, TRUE, DEFAULT_MAXNSLAVES, -1, 1000000, NULL, NULL) );
1799 
1800  /* include parameter matchingrate */
1801  SCIP_CALL( SCIPaddRealParam(scip, "heuristics/twoopt/matchingrate",
1802  "parameter to determine the percentage of rows two variables have to share before they are considered equal",
1803  &heurdata->matchingrate, TRUE, DEFAULT_MATCHINGRATE, 0.0, 1.0, NULL, NULL) );
1804 
1805  return SCIP_OKAY;
1806 }
#define SCIPfreeBlockMemoryArray(scip, ptr, num)
Definition: scip_mem.h:97
static SCIP_RETCODE shiftValues(SCIP *scip, SCIP_VAR *master, SCIP_VAR *slave, SCIP_Real mastersolval, DIRECTION masterdir, SCIP_Real slavesolval, DIRECTION slavedir, SCIP_Real shiftval, SCIP_Real *activities, int nrows, SCIP_Bool *feasible)
Definition: heur_twoopt.c:145
SCIP_RETCODE SCIPgetLPColsData(SCIP *scip, SCIP_COL ***cols, int *ncols)
Definition: scip_lp.c:462
#define SCIPreallocBlockMemoryArray(scip, ptr, oldnum, newnum)
Definition: scip_mem.h:86
Primal heuristic to improve incumbent solution by flipping pairs of variables.
SCIP_RETCODE SCIPfreeSol(SCIP *scip, SCIP_SOL **sol)
Definition: scip_sol.c:977
SCIP_Bool SCIProwIsLocal(SCIP_ROW *row)
Definition: lp.c:17250
SCIP_Bool SCIPisPositive(SCIP *scip, SCIP_Real val)
#define SCIPallocBlockMemoryArray(scip, ptr, num)
Definition: scip_mem.h:80
const char * SCIPheurGetName(SCIP_HEUR *heur)
Definition: heur.c:1429
SCIP_RETCODE SCIPsetSolVal(SCIP *scip, SCIP_SOL *sol, SCIP_VAR *var, SCIP_Real val)
Definition: scip_sol.c:1213
public methods for SCIP parameter handling
void SCIPfreeRandom(SCIP *scip, SCIP_RANDNUMGEN **randnumgen)
int SCIPgetNLPRows(SCIP *scip)
Definition: scip_lp.c:596
static SCIP_DECL_HEURFREE(heurFreeTwoopt)
Definition: heur_twoopt.c:828
SCIP_RETCODE SCIPsetHeurExitsol(SCIP *scip, SCIP_HEUR *heur, SCIP_DECL_HEUREXITSOL((*heurexitsol)))
Definition: scip_heur.c:233
public methods for memory management
SCIP_HEURDATA * SCIPheurGetData(SCIP_HEUR *heur)
Definition: heur.c:1340
SCIP_Real SCIPgetVarLbDive(SCIP *scip, SCIP_VAR *var)
Definition: scip_lp.c:2556
SCIP_EXPORT SCIP_Bool SCIPsolIsOriginal(SCIP_SOL *sol)
Definition: sol.c:2521
SCIP_Real * SCIPcolGetVals(SCIP_COL *col)
Definition: lp.c:17010
void SCIPwarningMessage(SCIP *scip, const char *formatstr,...)
Definition: scip_message.c:123
static long bound
SCIP_Real SCIPgetSolVal(SCIP *scip, SCIP_SOL *sol, SCIP_VAR *var)
Definition: scip_sol.c:1353
SCIP_RETCODE SCIPprintRow(SCIP *scip, SCIP_ROW *row, FILE *file)
Definition: scip_lp.c:2152
int SCIPcolGetNNonz(SCIP_COL *col)
Definition: lp.c:16975
#define DEFAULT_WAITINGNODES
Definition: heur_twoopt.c:59
#define DEFAULT_MAXNSLAVES
Definition: heur_twoopt.c:63
int SCIPgetNVars(SCIP *scip)
Definition: scip_prob.c:1986
#define DEFAULT_INTOPT
Definition: heur_twoopt.c:58
#define FALSE
Definition: def.h:73
SCIP_ROW ** SCIPcolGetRows(SCIP_COL *col)
Definition: lp.c:17000
static SCIP_RETCODE optimize(SCIP *scip, SCIP_SOL *worksol, SCIP_VAR **vars, int *blockstart, int *blockend, int nblocks, OPTTYPE opttype, SCIP_Real *activities, int nrows, SCIP_Bool *improvement, SCIP_Bool *varboundserr, SCIP_HEURDATA *heurdata)
Definition: heur_twoopt.c:908
SCIP_EXPORT SCIP_Real SCIPvarGetObj(SCIP_VAR *var)
Definition: var.c:17510
SCIP_EXPORT SCIP_HEUR * SCIPsolGetHeur(SCIP_SOL *sol)
Definition: sol.c:2604
#define HEUR_FREQ
Definition: heur_twoopt.c:50
SCIP_EXPORT SCIP_VARTYPE SCIPvarGetType(SCIP_VAR *var)
Definition: var.c:17177
#define TRUE
Definition: def.h:72
#define SCIPdebug(x)
Definition: pub_message.h:84
enum SCIP_Retcode SCIP_RETCODE
Definition: type_retcode.h:54
SCIP_RETCODE SCIPlinkLPSol(SCIP *scip, SCIP_SOL *sol)
Definition: scip_sol.c:1018
#define SCIPstatisticMessage
Definition: pub_message.h:114
SCIP_Real SCIPgetVarUbDive(SCIP *scip, SCIP_VAR *var)
Definition: scip_lp.c:2585
SCIP_RETCODE SCIPchgVarLbDive(SCIP *scip, SCIP_VAR *var, SCIP_Real newbound)
Definition: scip_lp.c:2359
SCIP_Bool SCIPisFeasLE(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
struct SCIP_HeurData SCIP_HEURDATA
Definition: type_heur.h:67
public methods for problem variables
SCIP_RETCODE SCIPaddBoolParam(SCIP *scip, const char *name, const char *desc, SCIP_Bool *valueptr, SCIP_Bool isadvanced, SCIP_Bool defaultvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip_param.c:48
#define SCIPfreeBlockMemory(scip, ptr)
Definition: scip_mem.h:95
#define HEUR_FREQOFS
Definition: heur_twoopt.c:51
static SCIP_DECL_SORTPTRCOMP(SCIPvarcolComp)
Definition: heur_twoopt.c:293
SCIP_EXPORT SCIP_VARSTATUS SCIPvarGetStatus(SCIP_VAR *var)
Definition: var.c:17131
#define HEUR_NAME
Definition: heur_twoopt.c:46
int SCIProwGetLPPos(SCIP_ROW *row)
Definition: lp.c:17350
#define HEUR_TIMING
Definition: heur_twoopt.c:54
#define SCIPfreeBufferArray(scip, ptr)
Definition: scip_mem.h:123
#define SCIPallocBlockMemory(scip, ptr)
Definition: scip_mem.h:78
SCIP_RETCODE SCIPsolveDiveLP(SCIP *scip, int itlim, SCIP_Bool *lperror, SCIP_Bool *cutoff)
Definition: scip_lp.c:2618
SCIP_RETCODE SCIPsetHeurInit(SCIP *scip, SCIP_HEUR *heur, SCIP_DECL_HEURINIT((*heurinit)))
Definition: scip_heur.c:185
SCIP_RETCODE SCIPtrySol(SCIP *scip, SCIP_SOL *sol, SCIP_Bool printreason, SCIP_Bool completely, SCIP_Bool checkbounds, SCIP_Bool checkintegrality, SCIP_Bool checklprows, SCIP_Bool *stored)
Definition: scip_sol.c:3125
#define SCIPdebugMsg
Definition: scip_message.h:69
SCIP_Bool SCIPisFeasIntegral(SCIP *scip, SCIP_Real val)
SCIP_LPSOLSTAT SCIPgetLPSolstat(SCIP *scip)
Definition: scip_lp.c:159
SCIP_Bool SCIPhasCurrentNodeLP(SCIP *scip)
Definition: scip_lp.c:74
SCIP_Bool SCIPisInfinity(SCIP *scip, SCIP_Real val)
static SCIP_DECL_HEURINITSOL(heurInitsolTwoopt)
Definition: heur_twoopt.c:1369
int SCIPgetNIntVars(SCIP *scip)
Definition: scip_prob.c:2076
public methods for numerical tolerances
SCIP_RETCODE SCIPcreateRandom(SCIP *scip, SCIP_RANDNUMGEN **randnumgen, unsigned int initialseed, SCIP_Bool useglobalseed)
Direction
Definition: heur_twoopt.c:128
public methods for querying solving statistics
SCIP_RETCODE SCIPincludeHeurBasic(SCIP *scip, SCIP_HEUR **heur, const char *name, const char *desc, char dispchar, int priority, int freq, int freqofs, int maxdepth, SCIP_HEURTIMING timingmask, SCIP_Bool usessubscip, SCIP_DECL_HEUREXEC((*heurexec)), SCIP_HEURDATA *heurdata)
Definition: scip_heur.c:108
#define DEFAULT_RANDSEED
Definition: heur_twoopt.c:65
static SCIP_DECL_HEURINIT(heurInitTwoopt)
Definition: heur_twoopt.c:848
SCIP_Longint SCIPgetNNodes(SCIP *scip)
SCIP_RETCODE SCIPcreateSolCopy(SCIP *scip, SCIP_SOL **sol, SCIP_SOL *sourcesol)
Definition: scip_sol.c:610
#define SCIPduplicateBlockMemoryArray(scip, ptr, source, num)
Definition: scip_mem.h:92
static SCIP_DECL_HEUREXIT(heurExitTwoopt)
Definition: heur_twoopt.c:1272
static SCIP_RETCODE presolveTwoOpt(SCIP *scip, SCIP_HEUR *heur, SCIP_HEURDATA *heurdata)
Definition: heur_twoopt.c:733
SCIP_EXPORT const char * SCIPvarGetName(SCIP_VAR *var)
Definition: var.c:17012
SCIP_EXPORT void SCIPsolSetHeur(SCIP_SOL *sol, SCIP_HEUR *heur)
Definition: sol.c:2649
SCIP_EXPORT SCIP_Bool SCIPvarIsIntegral(SCIP_VAR *var)
Definition: var.c:17203
void SCIPcolSort(SCIP_COL *col)
Definition: lp.c:3424
SCIP_RETCODE SCIPgetLPRowsData(SCIP *scip, SCIP_ROW ***rows, int *nrows)
Definition: scip_lp.c:540
SCIP_Bool SCIPisFeasEQ(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_RETCODE SCIPstartDive(SCIP *scip)
Definition: scip_lp.c:2182
SCIP_VAR ** SCIPgetVars(SCIP *scip)
Definition: scip_prob.c:1941
static SCIP_DECL_HEUREXEC(heurExecTwoopt)
Definition: heur_twoopt.c:1465
int SCIProwGetIndex(SCIP_ROW *row)
Definition: lp.c:17210
SCIP_Bool SCIPisZero(SCIP *scip, SCIP_Real val)
void SCIPheurSetData(SCIP_HEUR *heur, SCIP_HEURDATA *heurdata)
Definition: heur.c:1350
#define NULL
Definition: lpi_spx1.cpp:155
SCIP_EXPORT void SCIPsortRealPtrPtrInt(SCIP_Real *realarray, void **ptrarray1, void **ptrarray2, int *intarray, int len)
public methods for primal CIP solutions
static int varColCompare(SCIP_VAR *var1, SCIP_VAR *var2)
Definition: heur_twoopt.c:250
#define SCIP_CALL(x)
Definition: def.h:364
SCIP_Real SCIPfeasFloor(SCIP *scip, SCIP_Real val)
SCIP_EXPORT void SCIPsortPtr(void **ptrarray, SCIP_DECL_SORTPTRCOMP((*ptrcomp)), int len)
public methods for primal heuristic plugins and divesets
SCIP_Bool SCIPisFeasZero(SCIP *scip, SCIP_Real val)
SCIP_EXPORT SCIP_COL * SCIPvarGetCol(SCIP_VAR *var)
Definition: var.c:17376
#define SCIPallocBufferArray(scip, ptr, num)
Definition: scip_mem.h:111
public data structures and miscellaneous methods
int SCIPrandomGetInt(SCIP_RANDNUMGEN *randnumgen, int minrandval, int maxrandval)
Definition: misc.c:9945
SCIP_RETCODE SCIPendDive(SCIP *scip)
Definition: scip_lp.c:2231
#define SCIP_Bool
Definition: def.h:70
#define DEFAULT_ARRAYSIZE
Definition: heur_twoopt.c:64
SCIP_RETCODE SCIPsetHeurExit(SCIP *scip, SCIP_HEUR *heur, SCIP_DECL_HEUREXIT((*heurexit)))
Definition: scip_heur.c:201
#define HEUR_DESC
Definition: heur_twoopt.c:47
SCIP_EXPORT SCIP_Real SCIPvarGetUbGlobal(SCIP_VAR *var)
Definition: var.c:17672
#define MAX(x, y)
Definition: tclique_def.h:83
SCIP_Real SCIProwGetLhs(SCIP_ROW *row)
Definition: lp.c:17141
static SCIP_RETCODE innerPresolve(SCIP *scip, SCIP_VAR **vars, SCIP_VAR ***varspointer, int nvars, int *nblocks, int *maxblocksize, int *nblockvars, int **blockstart, int **blockend, SCIP_HEUR *heur, SCIP_HEURDATA *heurdata)
Definition: heur_twoopt.c:634
SCIP_RETCODE SCIPchgVarUbDive(SCIP *scip, SCIP_VAR *var, SCIP_Real newbound)
Definition: scip_lp.c:2391
public methods for LP management
SCIP_EXPORT int SCIPsolGetIndex(SCIP_SOL *sol)
Definition: sol.c:2635
SCIP_Bool SCIPisNegative(SCIP *scip, SCIP_Real val)
enum Direction DIRECTION
Definition: heur_twoopt.c:134
Opttype
Definition: heur_twoopt.c:120
SCIP_Bool SCIPisFeasGE(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_EXPORT SCIP_Real SCIPvarGetLbLocal(SCIP_VAR *var)
Definition: var.c:17718
SCIP_RETCODE SCIPaddRealParam(SCIP *scip, const char *name, const char *desc, SCIP_Real *valueptr, SCIP_Bool isadvanced, SCIP_Real defaultvalue, SCIP_Real minvalue, SCIP_Real maxvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip_param.c:130
#define DEFAULT_MATCHINGRATE
Definition: heur_twoopt.c:60
public methods for the LP relaxation, rows and columns
enum Opttype OPTTYPE
Definition: heur_twoopt.c:125
SCIP_EXPORT SCIP_Real SCIPvarGetUbLocal(SCIP_VAR *var)
Definition: var.c:17728
methods for sorting joint arrays of various types
SCIP_VAR ** b
Definition: circlepacking.c:56
static SCIP_DECL_HEURCOPY(heurCopyTwoopt)
Definition: heur_twoopt.c:814
#define HEUR_MAXDEPTH
Definition: heur_twoopt.c:52
SCIP_Bool SCIPisFeasGT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_Longint SCIPgetNLPIterations(SCIP *scip)
static void disposeVariable(SCIP_VAR **vars, int *blockend, int varindex)
Definition: heur_twoopt.c:619
public methods for solutions
public methods for random numbers
SCIP_EXPORT SCIP_Real SCIPvarGetLbGlobal(SCIP_VAR *var)
Definition: var.c:17662
SCIP_RETCODE SCIPsetHeurCopy(SCIP *scip, SCIP_HEUR *heur, SCIP_DECL_HEURCOPY((*heurcopy)))
Definition: scip_heur.c:153
SCIP_Bool SCIPisFeasLT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_EXPORT SCIP_Longint SCIPsolGetNodenum(SCIP_SOL *sol)
Definition: sol.c:2584
public methods for message output
SCIP_RETCODE SCIPgetVarsData(SCIP *scip, SCIP_VAR ***vars, int *nvars, int *nbinvars, int *nintvars, int *nimplvars, int *ncontvars)
Definition: scip_prob.c:1860
SCIP_RETCODE SCIPaddIntParam(SCIP *scip, const char *name, const char *desc, int *valueptr, SCIP_Bool isadvanced, int defaultvalue, int minvalue, int maxvalue, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip_param.c:74
SCIP_RETCODE SCIPprintSol(SCIP *scip, SCIP_SOL *sol, FILE *file, SCIP_Bool printzeros)
Definition: scip_sol.c:1767
#define SCIP_Real
Definition: def.h:163
#define HEUR_PRIORITY
Definition: heur_twoopt.c:49
const char * SCIProwGetName(SCIP_ROW *row)
Definition: lp.c:17200
public methods for message handling
#define HEUR_USESSUBSCIP
Definition: heur_twoopt.c:55
SCIP_RETCODE SCIPsetHeurInitsol(SCIP *scip, SCIP_HEUR *heur, SCIP_DECL_HEURINITSOL((*heurinitsol)))
Definition: scip_heur.c:217
int SCIPgetNBinVars(SCIP *scip)
Definition: scip_prob.c:2031
SCIP_RETCODE SCIPsetHeurFree(SCIP *scip, SCIP_HEUR *heur, SCIP_DECL_HEURFREE((*heurfree)))
Definition: scip_heur.c:169
SCIP_Real SCIProwGetRhs(SCIP_ROW *row)
Definition: lp.c:17151
public methods for primal heuristics
#define HEUR_DISPCHAR
Definition: heur_twoopt.c:48
public methods for global and local (sub)problems
static SCIP_DECL_HEUREXITSOL(heurExitsolTwoopt)
Definition: heur_twoopt.c:1402
SCIP_SOL * SCIPgetBestSol(SCIP *scip)
Definition: scip_sol.c:2305
SCIP_RETCODE SCIPincludeHeurTwoopt(SCIP *scip)
Definition: heur_twoopt.c:1763
static SCIP_Bool checkConstraintMatching(SCIP *scip, SCIP_VAR *var1, SCIP_VAR *var2, SCIP_Real matchingrate)
Definition: heur_twoopt.c:302
static SCIP_Real determineBound(SCIP *scip, SCIP_SOL *sol, SCIP_VAR *master, DIRECTION masterdirection, SCIP_VAR *slave, DIRECTION slavedirection, SCIP_Real *activities, int nrows)
Definition: heur_twoopt.c:394
#define SCIPreallocBufferArray(scip, ptr, num)
Definition: scip_mem.h:115
SCIP_Real SCIPgetRowSolActivity(SCIP *scip, SCIP_ROW *row, SCIP_SOL *sol)
Definition: scip_lp.c:2084
memory allocation routines