Scippy

SCIP

Solving Constraint Integer Programs

treemodel.c
Go to the documentation of this file.
1 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
2 /* */
3 /* This file is part of the program and library */
4 /* SCIP --- Solving Constraint Integer Programs */
5 /* */
6 /* Copyright (C) 2002-2021 Konrad-Zuse-Zentrum */
7 /* fuer Informationstechnik Berlin */
8 /* */
9 /* SCIP is distributed under the terms of the ZIB Academic License. */
10 /* */
11 /* You should have received a copy of the ZIB Academic License */
12 /* along with SCIP; see the file COPYING. If not email to scip@zib.de. */
13 /* */
14 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
15 
16 /**@file treemodel.c
17  * @brief Branching rules based on the Single-Variable-Branching (SVB) model
18  * @author Daniel Anderson
19  * @author Pierre Le Bodic
20  *
21  * The Single-Variable-Branching (SVB) model is a simplified model of
22  * Branch & Bound trees, from which several nontrivial variable selection
23  * rules arise. The Treemodel branching rule complements SCIP's hybrid
24  * branching by suggesting improved branching variables given the current
25  * pseudocosts and the current dual gap.
26  *
27  * Given a variable with dual bound changes (l, r) (both positive)
28  * and an absolute gap G, the SVB model describes the tree that needs to be
29  * built by branching on that same variable at every node until the value G
30  * is reached at every leaf, starting from 0 at the root node.
31  * If we do so for every variable, we can select the variable that produces
32  * the smallest tree.
33  * In the case where the gap is not known, then we can compute the growth rate
34  * of the tree, which we call the ratio.
35  * The ratio of a variable (l, r) is the factor by which the size of the tree
36  * built using (l, r) that closes a gap G must be multiplied by to close a gap
37  * G+1. This ratio is not constant for all gaps, but when G tends to infinity,
38  * it converges to a fixed value we can compute numerically using a root finding
39  * algorithm (e.g. Laguerre).
40  * The ratio is used when the gap is too large (e.g. no primal bound known) or
41  * to help approximate the size of the SVB tree for that variable.
42  *
43  * See the following publication for more detail:
44  *
45  * @par
46  * Pierre Le Bodic and George Nemhauser@n
47  * An abstract model for branching and its application to mixed integer programming@n
48  * Mathematical Programming, 2017@n
49  */
50 
51 /*---+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8----+----9----+----0----+----1----+----2*/
52 
53 #include "scip/treemodel.h"
54 
55 #include "scip/history.h"
56 #include "scip/var.h"
57 
58 #include <limits.h>
59 
60 #define LAGUERRE_THRESHOLD 100 /**< Maximum value of r/l at which Laguerre is the prefered FP method */
61 
62 /* Default parameters for the Treemodel branching rules */
63 #define DEFAULT_ENABLE FALSE /**< should candidate branching variables be scored using the Treemodel rule? */
64 #define DEFAULT_HIGHRULE 'r' /**< scoring function to use at nodes predicted to be high in the tree.
65  * ('d'efault, 's'vts, 'r'atio, 't'ree sample) */
66 #define DEFAULT_LOWRULE 'r' /**< scoring function to use at nodes predicted to be low in the tree
67  * ('d'efault, 's'vts, 'r'atio, 't'ree sample) */
68 #define DEFAULT_HEIGHT 10 /**< estimated tree height at which we switch from using the low rule to
69  * the high rule */
70 #define DEFAULT_FILTERHIGH 'a' /**< should dominated candidates be filtered before using the high scoring
71  * function? ('a'uto, 't'rue, 'f'alse) */
72 #define DEFAULT_FILTERLOW 'a' /**< should dominated candidates be filtered before using the low scoring
73  * function? ('a'uto, 't'rue, 'f'alse) */
74 #define DEFAULT_MAXFPITER 24 /**< maximum number of fixed-point iterations when computing the ratio */
75 #define DEFAULT_MAXSVTSHEIGHT 100 /**< maximum height to compute the SVTS score exactly before approximating */
76 #define DEFAULT_FALLBACKINF 'r' /**< which method should be used as a fallback if the tree size estimates are
77  * infinite? ('d'efault, 'r'atio) */
78 #define DEFAULT_FALLBACKNOPRIM 'r' /**< which method should be used as a fallback if there is no primal bound
79  * available? ('d'efault, 'r'atio) */
80 #define DEFAULT_SMALLPSCOST 0.1 /**< threshold at which pseudocosts are considered small, making hybrid scores
81  * more likely to be the deciding factor in branching */
82 
83 /** parameters required by the Treemodel branching rules */
85 {
86  SCIP_Bool enabled; /**< should candidate branching variables be scored using the Treemodel
87  * rule? */
88  char highrule; /**< scoring function to use at nodes predicted to be high in the tree.
89  * ('d'efault, 's'vts, 'r'atio, 't'ree sample) */
90  char lowrule; /**< scoring function to use at nodes predicted to be low in the tree
91  * ('d'efault, 's'vts, 'r'atio, 't'ree sample) */
92  int height; /**< estimated tree height at which we switch from using the low rule to
93  * the high rule */
94  char filterhigh; /**< should dominated candidates be filtered before using the high
95  * scoring function? ('a'uto, 't'rue, 'f'alse) [ADVANCED] */
96  char filterlow; /**< should dominated candidates be filtered before using the low
97  * scoring function? ('a'uto, 't'rue, 'f'alse) [ADVANCED] */
98  int maxfpiter; /**< maximum number of fixed-point iterations when computing the ratio
99  * [ADVANCED] */
100  int maxsvtsheight; /**< maximum height to compute the SVTS score exactly before approximating
101  * [ADVANCED] */
102  char fallbackinf; /**< which method should be used as a fallback if the tree size estimates
103  * are infinite? ('d'efault, 'r'atio) [ADVANCED] */
104  char fallbacknoprim; /**< which method should be used as a fallback if there is no primal bound
105  * available? ('d'efault, 'r'atio) [ADVANCED] */
106  SCIP_Real smallpscost; /**< threshold at which pseudocosts are considered small, making hybrid
107  * scores more likely to be the deciding factor in branching [ADVANCED] */
108 };
109 
110 /** branching encoding of a variable's ratio
111  * A variable's ratio is defined based upon its left and right LP gains, as the unique root > 1 of
112  * the polynomial x^r - x^(r-l) -1, where l and r are the left and right LP gains.
113  * We store the root as upratio^(invleft), with invleft = 1/l. The value upratio is thus
114  * the ratio of the variable (1, r/l).
115  * An extra boolean stores whether the encoded ratio is valid,
116  * i.e. there were no numerical problems when computing it */
117 struct SCIP_Ratio
118 {
119  SCIP_Real upratio; /**< "UnPowered" ratio, i.e. the ratio of the characteristic polynomial
120  * with gains (1, rightgain/leftgain) */
121  SCIP_Real invleft; /**< "INVerse left gain, i.e. 1/leftgain */
122  SCIP_Bool valid; /**< True iff the ratio computed is valid */
123 };
124 typedef struct SCIP_Ratio SCIP_RATIO;
126 /** a comparison method for the next method. It simply compares two SCIP_Real */
127 static
128 SCIP_DECL_SORTINDCOMP(sciprealcomp)
129 {
130  SCIP_Real* value = (SCIP_Real*) dataptr;
131  SCIP_Real diffval;
133  assert(value != NULL);
134  assert(ind1 >= 0 && ind2 >= 0);
135 
136  diffval = value[ind1] - value[ind2];
137  if( diffval < 0.0 )
138  return -1;
139  else if( diffval > 0.0)
140  return 1;
141  else
142  return 0;
143 }
144 
145 /** given a pair of arrays of real non-negative values (a,b), with a <= b, computes
146  * the pairs that belong to the pareto front (with a tolerance).
147  * In other words, we are looking for non-dominated pairs of values.
148  * One value and one array are computed after this method.
149  * The value is the number of non-dominated elements.
150  * The array is a boolean array that indicates if an element is dominated.
151  * In case of a draw, only one variable is considered as non-dominated.
152  */
153 static
155  SCIP* scip, /**< SCIP data structure */
156  SCIP_Real* a, /**< the first set of values */
157  SCIP_Real* b, /**< the second set of values */
158  int size, /**< the size of array a (and b) */
159  int* ndominated, /**< returns the number of dominated elements */
160  SCIP_Bool* dominated /**< returns the array of booleans that determine if an element is
161  * dominated */
162  )
163 {
164  SCIP_Real bestcurrenta;
165  SCIP_Real besta;
166  SCIP_Real currentb;
167  int* permb;
168  int* bestcurrents;
169  int nbestcurrent;
170  int indexinpermb;
171  int origindex;
172  int iterbestcurrent;
173 
174  assert(scip != NULL);
175  assert(a != NULL);
176  assert(b != NULL);
177  assert(ndominated != NULL);
178  assert(dominated != NULL);
179  assert(size > 0);
180 
181  SCIP_CALL( SCIPallocBufferArray(scip, &bestcurrents, size) );
182 
183  /* we first find the permutation of indices of array b that corresponds to
184  * the array of a non-increasing sort of its values */
185  SCIP_CALL( SCIPallocBufferArray(scip, &permb, size) );
186  for( origindex=0; origindex<size; ++origindex )
187  permb[origindex] = origindex;
188 
189  SCIPsortDownInd(permb, sciprealcomp, (void*)b, size);
190 
191  *ndominated = 0;
192  /* Now we will traverse the pair of arrays a and b by non-decreasing order of values of b
193  * and mark the (non) dominated pairs */
194 
195  /* The current max value of a for all pairs that (almost) have the same value b */
196  bestcurrenta = a[permb[0]];
197 
198  /* the current value b */
199  currentb = b[permb[0]];
200  /* the best pair(s) for the current value b */
201  bestcurrents[0] = permb[0];
202  nbestcurrent = 1;
203  /* the value a to "beat" to be non-dominated */
204  besta = -1;
205  for( indexinpermb = 1; indexinpermb < size; ++indexinpermb )
206  {
207  origindex = permb[indexinpermb];
208  assert(b[origindex] <= currentb);
209  if( SCIPisLT(scip, b[origindex], currentb) )
210  {
211  /* If the above is true, then we went through all the previous elements that had value currentb */
212  /* Thus the best element for value currentb is non-dominated if its value bestcurrenta is better
213  * than the previous best besta */
214  if( bestcurrenta > besta )
215  {
216  for( iterbestcurrent=0; iterbestcurrent < nbestcurrent; ++iterbestcurrent )
217  dominated[bestcurrents[iterbestcurrent]] = FALSE;
218 
219  besta = bestcurrenta;
220  }
221  else
222  {
223  for( iterbestcurrent = 0; iterbestcurrent < nbestcurrent; ++iterbestcurrent )
224  {
225  dominated[bestcurrents[iterbestcurrent]] = TRUE;
226  ++(*ndominated);
227  }
228  }
229  bestcurrenta = a[origindex];
230  currentb = b[origindex];
231  bestcurrents[0] = origindex;
232  nbestcurrent = 1;
233  }
234  else
235  {
236  /* Then the b values are (almost) equal and we need to compare values a */
237  if( SCIPisGT(scip, a[origindex], bestcurrenta) )
238  {
239  /* Then the new value is better than the old one(s) */
240  for( iterbestcurrent = 0; iterbestcurrent < nbestcurrent; ++iterbestcurrent )
241  {
242  dominated[bestcurrents[iterbestcurrent]] = TRUE;
243  ++(*ndominated);
244  }
245 
246  bestcurrenta = a[origindex];
247  bestcurrents[0] = origindex;
248  nbestcurrent = 1;
249  }
250  else
251  {
252  /* Then the new value is equal or dominated */
253  if( SCIPisEQ(scip, a[origindex], bestcurrenta) )
254  {
255  bestcurrents[nbestcurrent] = origindex;
256  ++nbestcurrent;
257  }
258  else
259  {
260  dominated[origindex] = TRUE;
261  ++(*ndominated);
262  }
263  }
264  }
265  }
266  /* Finally, we have to look at the last best variable */
267  if( bestcurrenta > besta )
268  {
269  for( iterbestcurrent = 0; iterbestcurrent < nbestcurrent; ++iterbestcurrent )
270  dominated[bestcurrents[iterbestcurrent]] = FALSE;
271  }
272  else
273  {
274  for( iterbestcurrent = 0; iterbestcurrent < nbestcurrent; ++iterbestcurrent )
275  {
276  dominated[bestcurrents[iterbestcurrent]] = TRUE;
277  ++(*ndominated);
278  }
279  }
280 
281  SCIPfreeBufferArray(scip, &permb);
282  SCIPfreeBufferArray(scip, &bestcurrents);
283  return SCIP_OKAY;
284 }
285 
286 /** returns true iff the variable with given gains has a ratio better (i.e smaller) than the given one */
287 static
289  SCIP* scip, /**< SCIP data structure */
290  SCIP_RATIO* branchratio, /**< The variable's ratio to compare against */
291  SCIP_Real leftgain, /**< the left gain of a variable */
292  SCIP_Real rightgain /**< the right gain of a variable */
293  )
294 {
295  SCIP_Real result;
297  assert(branchratio != NULL);
298  assert(branchratio->valid);
299  assert(SCIPisLE(scip, leftgain, rightgain));
300 
301  /* We evaluate the characteristic polynomial of the variable on the given ratio. */
302  result = -1;
303  if( leftgain > 0.0 && rightgain > 0.0 )
304  {
305  result = pow(branchratio->upratio, rightgain * branchratio->invleft) - pow(branchratio->upratio, (rightgain - leftgain) * branchratio->invleft) - 1; /*lint !e644*/
306  }
307 
308  /* If the result is positive, then it has a better ratio. */
309  return (result > 0.0);
310 }
311 
312 /** computes the variable ratio corresponding to the left and right gains */
313 static
314 void computeVarRatio(
315  SCIP* scip, /**< SCIP data structure */
316  SCIP_TREEMODEL* treemodel, /**< Treemodel parameter data structure */
317  SCIP_VAR* var, /**< the candidate branching variable */
318  SCIP_Real leftgain, /**< the left gain of the variable */
319  SCIP_Real rightgain, /**< the right gain of the variable */
320  SCIP_RATIO* branchratio /**< storage for the computed ratio */
321  )
322 {
323  SCIP_Real ratio;
324  SCIP_Real newratio;
325  SCIP_Real r;
326  int iters;
327 
328  assert(SCIPisGE(scip, leftgain, 0.0));
329  assert(SCIPisGE(scip, rightgain, leftgain));
330 
331  if( SCIPisZero(scip, leftgain) || SCIPisZero(scip, rightgain) )
332  {
333  branchratio->valid = FALSE;
334  return;
335  }
336 
337  /* We scale left and right gains by dividing both by left */
338  r = rightgain / leftgain;
339 
340  /* In the case where l and r are very close r may become < 1 */
341  if( r <= 1 )
342  {
343  branchratio->valid = TRUE;
344  branchratio->upratio = 2.0;
345  branchratio->invleft = 1.0 / leftgain;
346  return;
347  }
348 
349  /* Check if this ratio has already been computed */
351  {
352  branchratio->valid = TRUE;
353  branchratio->upratio = SCIPhistoryGetLastRatio(var->history);
354  branchratio->invleft = 1.0 / leftgain;
355  return;
356  }
357 
358  /* Initialise the ratio at the previously computed ratio (if applicable) otherwise
359  * use the lower bound 2^(1/r) <= phi <= 2^(1/l).
360  * Note that we only use the previous ratio if the previous value of r/l was larger,
361  * ie. the previous ratio was smaller since we want to initialise at a lower bound.
362  */
363  ratio = 1.0;
364  newratio = pow(2.0, 1.0/r);
366  && SCIPhistoryGetLastRatio(var->history) > newratio )
367  newratio = SCIPhistoryGetLastRatio(var->history);
368 
369  /* Depending on the value of rightgain/leftgain, we have two different methods to compute the ratio
370  * If this value is bigger than 100, we use a fixed-point method. Otherwise, we use Laguerre's method
371  * This is strictly for numerical efficiency and based on experiments.
372  */
373 
374  /* Use Laguerre's method */
375  if( r <= LAGUERRE_THRESHOLD )
376  {
377  /* We relax the epsilon after 5 iterations since we may not have enough precision to achieve any better
378  * convergence */
379  for( iters = 0; ((iters <= 5 && !SCIPisEQ(scip, ratio, newratio)) ||
380  (iters > 5 && !SCIPisSumEQ(scip, ratio, newratio)))
381  && iters < treemodel->maxfpiter && newratio > 1.0; iters++ )
382  {
383  double G, H, a, p, p1, p2, phi_r;
384 
385  ratio = newratio;
386  phi_r = pow(ratio, r);
387  p = phi_r - phi_r / ratio - 1.0;
388  if( p != 0 )
389  {
390  p1 = (r * phi_r - (r - 1.0) * phi_r / ratio) / ratio;
391  p2 = (r * (r - 1.0) * phi_r - (r - 1.0) * (r - 2.0) * phi_r / ratio) / ratio / ratio;
392  G = p1 / p;
393  H = G * G - (p2 / p);
394  a = r / (G + (G >= 0 ? 1.0 : -1.0) * sqrt((r - 1.0) * (r * H - G * G)));
395  newratio = ratio - a;
396  }
397  }
398  }
399  /* Use fixed point method */
400  else
401  {
402  /* We relax the epsilon after 10 iterations since we may not have enough precision to achieve any better
403  * convergence */
404  for( iters = 0; ((iters <= 10 && !SCIPisEQ(scip, ratio, newratio)) ||
405  (iters > 10 && !SCIPisSumEQ(scip, ratio, newratio)))
406  && iters < treemodel->maxfpiter && newratio > 1; iters++ )
407  {
408  ratio = newratio;
409  newratio = pow(1.0-1.0/ratio, -1.0/r);
410  }
411  }
412 
413  /* We think that everything worked.
414  * Note that the fixed point method is not guaranteed to converge due to numerical precision issues.
415  * In the case that the method fails to converge, a fallback strategy must be used.
416  * For instance, if this method is used for branching, then this variable can be ignored,
417  * or the scores of all variables could be recomputed using a different method. */
418  if( iters < treemodel->maxfpiter && newratio > 1.0 )
419  {
420  branchratio->valid = TRUE;
421  branchratio->upratio = (ratio + newratio) / 2.0;
422  branchratio->invleft = 1.0 / leftgain;
423  }
424  /* We (hopefully) make finding bugs easier by setting these values */
425  else
426  {
427  branchratio->valid = FALSE;
428  branchratio->upratio = -1.0;
429  branchratio->invleft = -1.0;
430  }
431 
432  /* Update the history */
433  SCIPhistorySetRatioHistory(var->history, branchratio->valid, branchratio->upratio, r);
434 }
435 
436 /** use the Ratio scoring function to select a branching candidate */
437 static
439  SCIP* scip, /**< SCIP data structure */
440  SCIP_TREEMODEL* treemodel, /**< Treemodel parameter data structure */
441  SCIP_VAR** branchcands, /**< branching candidate storage */
442  SCIP_Real* mingains, /**< minimum gain of rounding downwards or upwards */
443  SCIP_Real* maxgains, /**< maximum gain of rounding downwards or upwards */
444  SCIP_Bool filterdominated, /**< whether dominated variables have been filtered */
445  SCIP_Bool* dominated, /**< whether each variable is dominated or not */
446  int nbranchcands, /**< the number of branching candidates */
447  int* bestcand /**< the best branching candidate found before the call,
448  and the best candidate after the call (possibly the same) */
449  )
450 {
451  SCIP_RATIO branchratio;
452  SCIP_RATIO bestbranchratio;
453  int c;
454 
455  /* We initialize bestbranchratio at the default bestcand ratio, since it is likely to have
456  * a very good ratio and save evaluations of the ratio for many variables */
457  int referencevar = *bestcand;
458  computeVarRatio(scip, treemodel, branchcands[referencevar], mingains[referencevar], maxgains[referencevar], &bestbranchratio);
459 
460  for( c = 0; c < nbranchcands; ++c )
461  {
462  if( (!filterdominated || !dominated[c]) && c != referencevar )
463  {
464  if( !bestbranchratio.valid || hasBetterRatio(scip, &bestbranchratio, mingains[c], maxgains[c]) ) /*lint !e644*/
465  {
466  computeVarRatio(scip, treemodel, branchcands[c], mingains[c], maxgains[c], &branchratio);
467  if( branchratio.valid ) /*lint !e644*/
468  {
469  *bestcand = c;
470  bestbranchratio = branchratio;
471  }
472  }
473  }
474  }
475 
476  return SCIP_OKAY;
477 }
478 
479 /** Returns the predicted treesize for the gap and given up and down gains */
480 static
482  SCIP* scip, /**< SCIP data structure */
483  SCIP_TREEMODEL* treemodel, /**< Treemodel parameter data structure */
484  SCIP_VAR* var, /**< the candidate branching variable */
485  SCIP_Real absgap, /**< the absolute gap to close (typically the local gap at the current node) */
486  SCIP_Real mingain, /**< prediction of smaller objective gain of downwards/upwards */
487  SCIP_Real maxgain /**< prediction of larger objective gain of downwards/upwards */
488  )
489 {
490  SCIP_Real prediction = SCIP_REAL_MAX;
491 
492  if( SCIPisGT(scip, mingain, 0.0) && !SCIPisInfinity(scip, absgap) )
493  {
494  SCIP_Real treesize;
495  SCIP_Real gaptoreach;
496  SCIP_Real scaledgap;
497  SCIP_Real scaledgain;
498  int mindepth;
499  int nr;
500  int ir;
501 
502  /* We implicitly set the minimum gain to 1, and the maximum gain and gap accordingly,
503  * as the treesize does not change if we scale the gains and gap by a scalar */
504  scaledgain = maxgain / mingain;
505  scaledgap = absgap / mingain;
506 
507  mindepth = (int) SCIPceil(scip, scaledgap / scaledgain);
508 
509  /* In the following case we compute the treesize for a smaller gap
510  * and we will deduce the treesize of the scaledgap using the ratio */
511  if( mindepth > treemodel->maxsvtsheight )
512  {
513  gaptoreach = scaledgap * (treemodel->maxsvtsheight - 1) / mindepth;
514 
515  assert(!SCIPisInfinity(scip, gaptoreach));
516  assert(gaptoreach > scaledgain);
517  }
518  else
519  {
520  gaptoreach = scaledgap;
521  }
522 
523  mindepth = (int) ceil(gaptoreach / scaledgain);
524  assert(mindepth <= treemodel->maxsvtsheight);
525  treesize = 1;
526 
527  /* nr is the number of times we turn right to reach a leaf */
528  for( nr = 1; nr <= mindepth; ++nr )
529  {
530  SCIP_Real binomcoeff = 1.0;
531  for( ir = 1; ir <= nr; ++ir )
532  {
533  binomcoeff *= (nr + ceil((gaptoreach - (nr - 1) * scaledgain)) - ir) / ir;
534  }
535  treesize += binomcoeff;
536  }
537 
538  treesize = 2.0 * treesize - 1.0;
539 
540  assert(SCIPisGE(scip, treesize, 3.0));
541 
542  if( !SCIPisEQ(scip, scaledgap, gaptoreach) )
543  {
544  /* If we have not computed the treesize for the scaled gap but for max gap instead,
545  * we use the ratio between two iterations to come up with an estimate of the treesize
546  * for the scaled gap */
547  if( !SCIPisInfinity(scip,treesize) )
548  {
549  SCIP_RATIO branchratio;
550  computeVarRatio(scip, treemodel, var, mingain, maxgain, &branchratio);
551 
552  if( branchratio.valid ) /*lint !e644*/
553  prediction = treesize * pow(branchratio.upratio, (scaledgap - gaptoreach) * branchratio.invleft); /*lint !e644*/
554  }
555  }
556  else
557  {
558  prediction = treesize;
559  }
560  }
561 
562  return prediction;
563 }
564 
565 /** use the SVTS scoring function to select a branching candidate */
566 static
568  SCIP* scip, /**< SCIP data structure */
569  SCIP_TREEMODEL* treemodel, /**< Treemodel parameter data structure */
570  SCIP_VAR** branchcands, /**< branching candidate storage */
571  SCIP_Real* mingains, /**< minimum gain of rounding downwards or upwards */
572  SCIP_Real* maxgains, /**< maximum gain of rounding downwards or upwards */
573  SCIP_Real* tiebreakerscore, /**< scores to use for tie breaking */
574  SCIP_Real localabsgap, /**< The dual gap at the current node */
575  SCIP_Bool filterdominated, /**< whether dominated variables have been filtered */
576  SCIP_Bool* dominated, /**< whether each variable is dominated or not */
577  int nbranchcands, /**< the number of branching candidates */
578  int ndominated, /**< the number of dominated candidates */
579  int* bestcand /**< the best branching candidate found before the call,
580  and the best candidate after the call (possibly the same) */
581  )
582 {
583  SCIP_Real* treesizes;
584  SCIP_Real referencetreesize;
585  SCIP_Real score;
586  SCIP_Real bestscore;
587  SCIP_Real avgtreesize;
588  int besttscand;
589  int referencevar;
590  int c;
591 
592  /* We will first measure the treesize for scip's default variable. If it is infinite then we don't compute
593  * the treesize for other variables (even though it might be finite) and go directly to the fallback strategy */
594  besttscand = *bestcand;
595  referencevar = *bestcand;
596 
597  treesizes = NULL;
598  bestscore = 0.0;
599  avgtreesize = 0.0;
600  if( !SCIPisInfinity(scip, localabsgap) )
601  {
602  referencetreesize = computeSVTS(scip, treemodel, branchcands[referencevar], localabsgap, mingains[referencevar],
603  maxgains[referencevar]);
604  if( !SCIPisInfinity(scip, referencetreesize) )
605  {
606  SCIP_CALL( SCIPallocBufferArray(scip, &treesizes, nbranchcands) );
607  treesizes[referencevar] = referencetreesize;
608 
609  for( c = 0; c < nbranchcands; ++c )
610  {
611  if( !filterdominated || !dominated[c] )
612  {
613  if( c != referencevar )
614  treesizes[c] = computeSVTS(scip, treemodel, branchcands[c], localabsgap, mingains[c], maxgains[c]);
615  else
616  treesizes[c] = referencetreesize;
617 
618  avgtreesize += treesizes[c];
619  }
620  else
621  treesizes[c] = SCIP_REAL_MAX;
622  }
623  avgtreesize = avgtreesize / (nbranchcands - ndominated);
624 
625  for( c = 0; c < nbranchcands; ++c )
626  {
627  score = (1.0 - 1.0 / (1.0 + avgtreesize / treesizes[c])) + 0.01 * tiebreakerscore[c];
628  if(score > bestscore)
629  {
630  bestscore = score;
631  besttscand = c;
632  }
633  }
634 
635  *bestcand = besttscand;
636 
637  SCIPfreeBufferArray(scip, &treesizes);
638  }
639  /* Apply infinite treesize fallback strategy */
640  else if( treemodel->fallbackinf == 'r' )
641  {
642  SCIP_CALL( selectCandidateUsingRatio(scip, treemodel, branchcands, mingains, maxgains, filterdominated, dominated,
643  nbranchcands, bestcand) );
644  }
645  }
646  /* Apply no primal bound fallback strategy */
647  else if( treemodel->fallbacknoprim == 'r' )
648  {
649  SCIP_CALL( selectCandidateUsingRatio(scip, treemodel, branchcands, mingains, maxgains, filterdominated, dominated,
650  nbranchcands, bestcand) );
651  }
652 
653  return SCIP_OKAY;
654 }
655 
656 /** computes a^b for integer b */
657 static
659  SCIP_Real a, /**< the base */
660  int b /**< the integer exponent */
661  )
662 { /*lint --e{644}*/
663  SCIP_Real ans;
664 
665  ans = 1.0;
666  for( ; b; b /= 2 )
667  {
668  if( b & 1 )
669  ans *= a;
670  a *= a;
671  }
672  return ans;
673 }
674 
675 /** returns the sampled tree size for the given lp gains and dual gap */
676 static
678  SCIP* scip, /**< SCIP data structure */
679  SCIP_TREEMODEL* treemodel, /**< Treemodel parameter data structure */
680  SCIP_VAR* var, /**< the candidate branching variable */
681  SCIP_Real absgap, /**< the absolute gap to close (typically the local at the current node) */
682  SCIP_Real leftgain, /**< The minimum gain from branching on this variable */
683  SCIP_Real rightgain /**< The maximum gain from branching on this variable */
684  )
685 {
686  SCIP_RATIO branchratio;
687  SCIP_Real prediction;
688  SCIP_Real leftsize;
689  SCIP_Real rightsize;
690  SCIP_Real midsize;
691 
692  computeVarRatio(scip, treemodel, var, leftgain, rightgain, &branchratio);
693 
694  if( branchratio.valid ) /*lint !e644*/
695  { /*lint --e{644}*/
696  SCIP_Real phi_l = branchratio.upratio;
697  SCIP_Real phi_r = pow(branchratio.upratio, rightgain * branchratio.invleft);
698  int kl = (int)ceil(absgap / leftgain);
699  int kr = (int)ceil(absgap / rightgain);
700  int k = (int)ceil(absgap / (leftgain + rightgain));
701  SCIP_Real phi_lr = phi_l * phi_r;
702  SCIP_Real phi_klr = integerpow(phi_lr, k);
703 
704  /* We compute an estimate of the size of the tree using the left-most leaf,
705  * right-most leaf, and the leaf obtained from alternating left and right. */
706  leftsize = (integerpow(phi_l, kl + 1) - 1.0) / (phi_l - 1.0);
707  rightsize = (integerpow(phi_r, kr + 1) - 1.0) / (phi_r - 1.0);
708 
709  if( k * (leftgain + rightgain) < absgap + rightgain )
710  midsize = (1.0 + phi_l) * (phi_klr * phi_lr - 1.0) / (phi_lr - 1.0) - phi_klr * phi_l;
711  else
712  midsize = (1.0 + phi_l) * (phi_klr - 1.0) / (phi_lr - 1.0);
713 
714  prediction = (leftsize + rightsize + midsize) / 3.0;
715  }
716  else
717  {
718  prediction = SCIP_REAL_MAX;
719  }
720 
721  return prediction;
722 }
723 
724 /** use the Tree Sampling scoring function to select a branching candidate */
725 static
727  SCIP* scip, /**< SCIP data structure */
728  SCIP_TREEMODEL* treemodel, /**< Treemodel parameter data structure */
729  SCIP_VAR** branchcands, /**< branching candidate storage */
730  SCIP_Real* mingains, /**< minimum gain of rounding downwards or upwards */
731  SCIP_Real* maxgains, /**< maximum gain of rounding downwards or upwards */
732  SCIP_Real* tiebreakerscore, /**< scores to use for tie breaking */
733  SCIP_Real localabsgap, /**< The dual gap at the current node */
734  SCIP_Bool filterdominated, /**< whether dominated variables have been filtered */
735  SCIP_Bool* dominated, /**< whether each variable is dominated or not */
736  int nbranchcands, /**< the number of branching candidates */
737  int ndominated, /**< the number of dominated candidates */
738  int* bestcand /**< the best branching candidate found before the call,
739  and the best candidate after the call (possibly the same) */
740  )
741 {
742  SCIP_Real* treesizes;
743  SCIP_Real referencetreesize;
744  SCIP_Real score;
745  SCIP_Real bestscore;
746  SCIP_Real avgtreesize;
747  int besttscand;
748  int referencevar;
749  int c;
750 
751  /* We will first measure the treesize for scip's default variable. If it is infinite then we don't compute
752  * the treesize for other variables (even though it might be finite) and go directly to the fallback strategy */
753  besttscand = *bestcand;
754  referencevar = *bestcand;
755 
756  treesizes = NULL;
757  bestscore = 0.0;
758  avgtreesize = 0.0;
759  if( !SCIPisInfinity(scip, localabsgap) )
760  {
761  referencetreesize = computeSampleTreesize(scip, treemodel, branchcands[referencevar], localabsgap, mingains[referencevar],
762  maxgains[referencevar]);
763 
764  if( !SCIPisInfinity(scip, referencetreesize) )
765  {
766  SCIP_CALL( SCIPallocBufferArray(scip, &treesizes, nbranchcands) );
767  treesizes[referencevar] = referencetreesize;
768 
769  for( c = 0; c < nbranchcands; ++c )
770  {
771  if( !filterdominated || !dominated[c] )
772  {
773  if( c != referencevar )
774  treesizes[c] = computeSampleTreesize(scip, treemodel, branchcands[c], localabsgap, mingains[c], maxgains[c]);
775  else
776  treesizes[c] = referencetreesize;
777 
778  avgtreesize += treesizes[c];
779  }
780  else
781  treesizes[c] = SCIP_REAL_MAX;
782  }
783  avgtreesize = avgtreesize / (nbranchcands - ndominated);
784 
785  for( c = 0; c < nbranchcands; ++c )
786  {
787  score = (1.0 - 1.0 / (1.0 + avgtreesize / treesizes[c])) + 0.01 * tiebreakerscore[c];
788  if( score > bestscore )
789  {
790  bestscore = score;
791  besttscand = c;
792  }
793  }
794 
795  *bestcand = besttscand;
796 
797  SCIPfreeBufferArray(scip, &treesizes);
798  }
799  /* Apply infinite treesize fallback strategy */
800  else if( treemodel->fallbackinf == 'r' )
801  {
802  SCIP_CALL( selectCandidateUsingRatio(scip, treemodel, branchcands, mingains, maxgains, filterdominated, dominated,
803  nbranchcands, bestcand) );
804  }
805  }
806  /* Apply no primal bound fallback strategy */
807  else if( treemodel->fallbacknoprim == 'r' )
808  {
809  SCIP_CALL( selectCandidateUsingRatio(scip, treemodel, branchcands, mingains, maxgains, filterdominated, dominated,
810  nbranchcands, bestcand) );
811  }
812 
813  return SCIP_OKAY;
814 }
815 
816 /** initialises the Treemodel parameter data structure */
818  SCIP* scip, /**< SCIP data structure */
819  SCIP_TREEMODEL** treemodel /**< Treemodel parameter data structure */
820  )
821 {
822  assert(treemodel != NULL);
823  SCIP_CALL( SCIPallocBlockMemory(scip, treemodel) );
824  assert(*treemodel != NULL);
826  SCIP_CALL( SCIPaddBoolParam(scip, "branching/treemodel/enable",
827  "should candidate branching variables be scored using the Treemodel branching rules?",
828  &(*treemodel)->enabled, FALSE, DEFAULT_ENABLE,
829  NULL, NULL) );
830  SCIP_CALL( SCIPaddCharParam(scip, "branching/treemodel/highrule",
831  "scoring function to use at nodes predicted to be high in the tree ('d'efault, 's'vts, 'r'atio, 't'ree sample)",
832  &(*treemodel)->highrule, FALSE, DEFAULT_HIGHRULE, "dsrt",
833  NULL, NULL) );
834  SCIP_CALL( SCIPaddCharParam(scip, "branching/treemodel/lowrule",
835  "scoring function to use at nodes predicted to be low in the tree ('d'efault, 's'vts, 'r'atio, 't'ree sample)",
836  &(*treemodel)->lowrule, FALSE, DEFAULT_LOWRULE, "dsrt",
837  NULL, NULL) );
838  SCIP_CALL( SCIPaddIntParam(scip, "branching/treemodel/height",
839  "estimated tree height at which we switch from using the low rule to the high rule",
840  &(*treemodel)->height, FALSE, DEFAULT_HEIGHT, 0, INT_MAX,
841  NULL, NULL) );
842  SCIP_CALL( SCIPaddCharParam(scip, "branching/treemodel/filterhigh",
843  "should dominated candidates be filtered before using the high scoring function? ('a'uto, 't'rue, 'f'alse)",
844  &(*treemodel)->filterhigh, TRUE, DEFAULT_FILTERHIGH, "atf",
845  NULL, NULL) );
846  SCIP_CALL( SCIPaddCharParam(scip, "branching/treemodel/filterlow",
847  "should dominated candidates be filtered before using the low scoring function? ('a'uto, 't'rue, 'f'alse)",
848  &(*treemodel)->filterlow, TRUE, DEFAULT_FILTERLOW, "atf",
849  NULL, NULL) );
850  SCIP_CALL( SCIPaddIntParam(scip, "branching/treemodel/maxfpiter",
851  "maximum number of fixed-point iterations when computing the ratio",
852  &(*treemodel)->maxfpiter, TRUE, DEFAULT_MAXFPITER, 1, INT_MAX,
853  NULL, NULL) );
854  SCIP_CALL( SCIPaddIntParam(scip, "branching/treemodel/maxsvtsheight",
855  "maximum height to compute the SVTS score exactly before approximating",
856  &(*treemodel)->maxsvtsheight, TRUE, DEFAULT_MAXSVTSHEIGHT, 0, INT_MAX,
857  NULL, NULL) );
858  SCIP_CALL( SCIPaddCharParam(scip, "branching/treemodel/fallbackinf",
859  "which method should be used as a fallback if the tree size estimates are infinite? ('d'efault, 'r'atio)",
860  &(*treemodel)->fallbackinf, TRUE, DEFAULT_FALLBACKINF, "dr",
861  NULL, NULL) );
862  SCIP_CALL( SCIPaddCharParam(scip, "branching/treemodel/fallbacknoprim",
863  "which method should be used as a fallback if there is no primal bound available? ('d'efault, 'r'atio)",
864  &(*treemodel)->fallbacknoprim, TRUE, DEFAULT_FALLBACKNOPRIM, "dr",
865  NULL, NULL) );
866  SCIP_CALL ( SCIPaddRealParam(scip, "branching/treemodel/smallpscost",
867  "threshold at which pseudocosts are considered small, making hybrid scores more likely to be the deciding factor in branching",
868  &(*treemodel)->smallpscost, TRUE, DEFAULT_SMALLPSCOST,
869  0.0, SCIP_REAL_MAX, NULL, NULL) );
870 
871  return SCIP_OKAY;
872 }
873 
874 /** frees the Treemodel parameter data structure */
876  SCIP* scip, /**< SCIP data structure */
877  SCIP_TREEMODEL** treemodel /**< Treemodel parameter data structure */
878  )
879 {
880  assert(treemodel != NULL);
881  assert(*treemodel != NULL);
882 
883  SCIPfreeBlockMemory(scip, treemodel);
884 
885  assert(*treemodel == NULL);
886 
887  return SCIP_OKAY;
888 }
889 
890 /** returns TRUE if the Treemodel branching rules are enabled */
892  SCIP* scip, /**< SCIP data structure */
893  SCIP_TREEMODEL* treemodel /**< Treemodel parameter data structure */
894  )
895 {
896  assert(scip != NULL);
897  return treemodel->enabled;
898 }
900 /** apply the Treemodel branching rules to attempt to select a better
901  * branching candidate than the one selected by pseudocost branching
902  */
904  SCIP* scip, /**< SCIP data structure */
905  SCIP_TREEMODEL* treemodel, /**< Treemodel parameter data structure */
906  SCIP_VAR** branchcands, /**< branching candidate storage */
907  SCIP_Real* mingains, /**< minimum gain of rounding downwards or upwards */
908  SCIP_Real* maxgains, /**< maximum gain of rounding downwards or upwards */
909  SCIP_Real* tiebreakerscore, /**< scores to use for tie breaking */
910  int nbranchcands, /**< the number of branching candidates */
911  int* bestcand /**< the best branching candidate found before the call,
912  and the best candidate after the call (possibly the same) */
913  )
914 {
915  SCIP_Real localabsgap; /* The gap at the current node */
916  int bestcandheight; /* The height of the best candidate according to SCIP */
917  char scoringfunction; /* Scoring function to use (based on the estimated tree height) */
918  char filtersetting; /* Whether we should apply filtering of dominated variables */
919 
920  assert(treemodel != NULL);
921  assert(treemodel->enabled);
922  assert(*bestcand >= 0);
923 
924  /* Compute the dual gap at the current node */
925  if( !SCIPisInfinity(scip, SCIPgetUpperbound(scip)) )
926  localabsgap = SCIPgetUpperbound(scip) - SCIPgetNodeLowerbound(scip, SCIPgetCurrentNode(scip));
927  else
928  localabsgap = SCIPinfinity(scip);
929 
930  /* Compute an estimate of the height of the current node using the bestcand variable */
931  if( !SCIPisInfinity(scip, localabsgap) && SCIPisGT(scip, mingains[*bestcand], 0.0)
932  && SCIPisLT(scip, localabsgap/mingains[*bestcand], 1.0 * INT_MAX))
933  bestcandheight = (int)(localabsgap/mingains[*bestcand]);
934  else
935  bestcandheight = INT_MAX;
936 
937  /* Decide which scoring function to use based on the estimated height of the tree */
938  if( bestcandheight < treemodel->height )
939  {
940  scoringfunction = treemodel->lowrule;
941  filtersetting = treemodel->filterlow;
942  }
943  else
944  {
945  scoringfunction = treemodel->highrule;
946  filtersetting = treemodel->filterhigh;
947  }
948 
949  /* We are going to apply a Treemodel variable selection rule */
950  if( scoringfunction != 'd' )
951  {
952  SCIP_Bool* dominated; /* Whether variables are dominated */
953  SCIP_Bool autofilter; /* If auto filtering is chosen, should variables be filtered? */
954  SCIP_Bool filterdominated; /* Whether we should filter dominated variables */
955  int ndominated; /* Number of dominated variables */
956 
957  /* Filtering dominated variables is suggested for SVTS and Tree Sampling rules */
958  autofilter = (filtersetting == 'a' && (scoringfunction == 's' || scoringfunction == 't'));
959  filterdominated = (autofilter || filtersetting == 't');
960 
961  /* If selected, find the dominated variables */
962  if( filterdominated )
963  {
964  SCIP_CALL( SCIPallocBufferArray(scip, &dominated, nbranchcands) );
965  SCIP_CALL( findNonDominatedVars(scip, mingains, maxgains, nbranchcands, &ndominated, dominated) );
966  }
967  else
968  {
969  dominated = NULL;
970  ndominated = 0;
971  }
972 
973  /* Invoke the selected scoring function */
974  switch( scoringfunction )
975  {
976  case 's':
977  SCIP_CALL( selectCandidateUsingSVTS(scip, treemodel, branchcands, mingains, maxgains, tiebreakerscore,
978  localabsgap, filterdominated, dominated, nbranchcands, ndominated, bestcand) );
979  break;
980  case 'r':
981  SCIP_CALL( selectCandidateUsingRatio(scip, treemodel, branchcands, mingains, maxgains, filterdominated,
982  dominated, nbranchcands, bestcand) );
983  break;
984  case 't':
985  SCIP_CALL( selectCandidateUsingSampling(scip, treemodel, branchcands, mingains, maxgains, tiebreakerscore,
986  localabsgap, filterdominated, dominated, nbranchcands, ndominated, bestcand) );
987  break;
988  default:
989  return SCIP_PARAMETERWRONGVAL;
990  }
991 
992  /* Free dominated variable buffer if it was used */
993  if( filterdominated )
994  {
995  assert(dominated != NULL);
996  SCIPfreeBufferArray(scip, &dominated);
997  }
998  }
999 
1000  return SCIP_OKAY;
1001 }
SCIP_Bool SCIPisEQ(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_Bool SCIPisSumEQ(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_Bool SCIPisGE(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
#define DEFAULT_FILTERHIGH
Definition: treemodel.c:73
#define DEFAULT_MAXSVTSHEIGHT
Definition: treemodel.c:80
SCIP_Bool enabled
Definition: treemodel.c:94
SCIPInterval pow(const SCIPInterval &x, const SCIPInterval &y)
SCIP_Real SCIPgetNodeLowerbound(SCIP *scip, SCIP_NODE *node)
Definition: scip_prob.c:3616
SCIP_Bool SCIPhistoryIsRatioValid(SCIP_HISTORY *history)
Definition: history.c:701
static SCIP_Real computeSampleTreesize(SCIP *scip, SCIP_TREEMODEL *treemodel, SCIP_VAR *var, SCIP_Real absgap, SCIP_Real leftgain, SCIP_Real rightgain)
Definition: treemodel.c:685
static SCIP_RETCODE findNonDominatedVars(SCIP *scip, SCIP_Real *a, SCIP_Real *b, int size, int *ndominated, SCIP_Bool *dominated)
Definition: treemodel.c:162
SCIP_NODE * SCIPgetCurrentNode(SCIP *scip)
Definition: scip_tree.c:81
SCIP_Real smallpscost
Definition: treemodel.c:114
#define FALSE
Definition: def.h:73
char fallbackinf
Definition: treemodel.c:110
#define TRUE
Definition: def.h:72
enum SCIP_Retcode SCIP_RETCODE
Definition: type_retcode.h:54
Branching rules based on the Single-Variable-Branching (SVB) model.
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
SCIP_Real SCIPceil(SCIP *scip, SCIP_Real val)
#define SCIPfreeBlockMemory(scip, ptr)
Definition: scip_mem.h:95
SCIP_Real SCIPgetUpperbound(SCIP *scip)
SCIP_Real SCIPhistoryGetLastRatio(SCIP_HISTORY *history)
Definition: history.c:711
#define SCIPfreeBufferArray(scip, ptr)
Definition: scip_mem.h:123
#define SCIPallocBlockMemory(scip, ptr)
Definition: scip_mem.h:78
SCIP_Bool SCIPisInfinity(SCIP *scip, SCIP_Real val)
internal methods for branching and inference history
SCIP_RETCODE SCIPtreemodelSelectCandidate(SCIP *scip, SCIP_TREEMODEL *treemodel, SCIP_VAR **branchcands, SCIP_Real *mingains, SCIP_Real *maxgains, SCIP_Real *tiebreakerscore, int nbranchcands, int *bestcand)
Definition: treemodel.c:911
#define DEFAULT_FALLBACKINF
Definition: treemodel.c:81
#define DEFAULT_FILTERLOW
Definition: treemodel.c:76
char fallbacknoprim
Definition: treemodel.c:112
SCIP_Bool SCIPisLE(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
#define DEFAULT_SMALLPSCOST
Definition: treemodel.c:87
static SCIP_Real computeSVTS(SCIP *scip, SCIP_TREEMODEL *treemodel, SCIP_VAR *var, SCIP_Real absgap, SCIP_Real mingain, SCIP_Real maxgain)
Definition: treemodel.c:489
SCIP_EXPORT void SCIPsortDownInd(int *indarray, SCIP_DECL_SORTINDCOMP((*indcomp)), void *dataptr, int len)
#define DEFAULT_FALLBACKNOPRIM
Definition: treemodel.c:84
SCIP_Bool valid
Definition: treemodel.c:130
SCIPInterval sqrt(const SCIPInterval &x)
SCIP_Real upratio
Definition: treemodel.c:127
SCIP_Bool SCIPisZero(SCIP *scip, SCIP_Real val)
#define NULL
Definition: lpi_spx1.cpp:155
static void computeVarRatio(SCIP *scip, SCIP_TREEMODEL *treemodel, SCIP_VAR *var, SCIP_Real leftgain, SCIP_Real rightgain, SCIP_RATIO *branchratio)
Definition: treemodel.c:322
#define SCIP_CALL(x)
Definition: def.h:370
SCIP_Bool SCIPtreemodelIsEnabled(SCIP *scip, SCIP_TREEMODEL *treemodel)
Definition: treemodel.c:899
internal methods for problem variables
#define DEFAULT_HIGHRULE
Definition: treemodel.c:64
#define SCIPallocBufferArray(scip, ptr, num)
Definition: scip_mem.h:111
SCIP_Real SCIPinfinity(SCIP *scip)
#define DEFAULT_HEIGHT
Definition: treemodel.c:70
static SCIP_Real integerpow(SCIP_Real a, int b)
Definition: treemodel.c:666
#define SCIP_Bool
Definition: def.h:70
#define DEFAULT_ENABLE
Definition: treemodel.c:63
SCIP_RETCODE SCIPtreemodelFree(SCIP *scip, SCIP_TREEMODEL **treemodel)
Definition: treemodel.c:883
static SCIP_RETCODE selectCandidateUsingSVTS(SCIP *scip, SCIP_TREEMODEL *treemodel, SCIP_VAR **branchcands, SCIP_Real *mingains, SCIP_Real *maxgains, SCIP_Real *tiebreakerscore, SCIP_Real localabsgap, SCIP_Bool filterdominated, SCIP_Bool *dominated, int nbranchcands, int ndominated, int *bestcand)
Definition: treemodel.c:575
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_LOWRULE
Definition: treemodel.c:67
#define SCIP_REAL_MAX
Definition: def.h:164
SCIP_Real * r
Definition: circlepacking.c:50
SCIP_VAR ** b
Definition: circlepacking.c:56
static SCIP_DECL_SORTINDCOMP(sciprealcomp)
Definition: treemodel.c:136
SCIP_VAR * a
Definition: circlepacking.c:57
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
static SCIP_RETCODE selectCandidateUsingRatio(SCIP *scip, SCIP_TREEMODEL *treemodel, SCIP_VAR **branchcands, SCIP_Real *mingains, SCIP_Real *maxgains, SCIP_Bool filterdominated, SCIP_Bool *dominated, int nbranchcands, int *bestcand)
Definition: treemodel.c:446
#define SCIP_Real
Definition: def.h:163
SCIP_Bool SCIPisLT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_Bool SCIPisGT(SCIP *scip, SCIP_Real val1, SCIP_Real val2)
SCIP_Real invleft
Definition: treemodel.c:129
void SCIPhistorySetRatioHistory(SCIP_HISTORY *history, SCIP_Bool valid, SCIP_Real ratio, SCIP_Real balance)
Definition: history.c:733
SCIP_Real SCIPhistoryGetLastBalance(SCIP_HISTORY *history)
Definition: history.c:722
static SCIP_Bool hasBetterRatio(SCIP *scip, SCIP_RATIO *branchratio, SCIP_Real leftgain, SCIP_Real rightgain)
Definition: treemodel.c:296
SCIP_HISTORY * history
Definition: struct_var.h:241
SCIP_RETCODE SCIPtreemodelInit(SCIP *scip, SCIP_TREEMODEL **treemodel)
Definition: treemodel.c:825
#define DEFAULT_MAXFPITER
Definition: treemodel.c:79
#define LAGUERRE_THRESHOLD
Definition: treemodel.c:60
static SCIP_RETCODE selectCandidateUsingSampling(SCIP *scip, SCIP_TREEMODEL *treemodel, SCIP_VAR **branchcands, SCIP_Real *mingains, SCIP_Real *maxgains, SCIP_Real *tiebreakerscore, SCIP_Real localabsgap, SCIP_Bool filterdominated, SCIP_Bool *dominated, int nbranchcands, int ndominated, int *bestcand)
Definition: treemodel.c:734
SCIP_RETCODE SCIPaddCharParam(SCIP *scip, const char *name, const char *desc, char *valueptr, SCIP_Bool isadvanced, char defaultvalue, const char *allowedvalues, SCIP_DECL_PARAMCHGD((*paramchgd)), SCIP_PARAMDATA *paramdata)
Definition: scip_param.c:158