Did you know ... | Search Documentation: |
Pack clpBNR -- prolog/clpBNR_toolkit.pl |
CLP(BNR) (library(clpBNR)
)is a CLP over the domain of real numbers extended with ±∞. This module contains a number of useful utilities for specific problem domains like the optimization of linear systems, enforcing local optima conditions, and constructing centre form contractors to improve performance (e.g., Taylor extensions of constraints). For more detailed discussion, see A Guide to CLP(BNR) (HTML version included with this pack in directory docs/
).
Documentation for exported predicates follows. The "custom" types include:
clpBNR
attributesmall/2
and Goal midsplit/1
:
?- X::real(-1,1),iterate_until(10,small(X,0),mid_split(X)),format("X = ~w\n",X),fail;true. X = _6288{real(-1,-1r2)} X = _6288{real(-1r2,0)} X = _6288{real(0,1r2)} X = _6288{real(1r2,1)} true.
The specific intended use case is to provide an iterator for meta-contractors such as the centre-form contractor such as midsplit/1
(example above) or as constructed by taylor_contractor/2
as in:
?- X::real,taylor_contractor({X**4-4*X**3+4*X**2-4*X+3==0},T), iterate_until(50,small(X),(T,mid_split_one([X]))),format("X = ~w\n",X),fail;true. X = _150{real(0.999999999926943,1.00000000007306)} X = _150{real(2.999999999484828,3.0000000005152105)} true.
(Aside: For some problems, solving with Taylor contractors can be a faster and more precise alternative to clpBNR:solve/1
.)
mid_split
for details of interval splitting for this predicate.
mid_split(X) :- M is midpoint(X), ({X=<M} ; {M=<X}).
Note that mid_split
succeeds if X is a number, but doesn't do anything.
Use clpBNR:small
as a pre-test to avoid splitting intervals which are already small enough.
taylor_contractor
. In normal usage, a direct call to cf_contractor
does appear; instead use cf_contractor
or in a Goal
for iterate_until/3
.
clpBNR_default_precision
); otherwise fails.
This is done by using iterate_until/3
limited to a count determined by the flag clpBNR_iteration_limit
. Examples:
?- X::real, taylor_contractor({X**4-4*X**3+4*X**2-4*X+3==0},T), cf_solve(T). T = cf_contractor([X], [_A]), X:: 1.000000000..., _A::real(-1.0Inf, 1.0Inf) ; T = cf_contractor([X], [_A]), X:: 3.00000000..., _A::real(-1.0Inf, 1.0Inf) ; false. ?- taylor_contractor({2*X1+5*X1**3+1==X2*(1+X2), 2*X2+5*X2**3+1==X1*(1+X1)},T), cf_solve(T). T = cf_contractor([X2, X1], [_A, _B]), X1:: -0.42730462..., X2:: -0.42730462..., _B::real(-1.0Inf, 1.0Inf), _A::real(-1.0Inf, 1.0Inf) ; false.
==
or =:=
) constraints Constraints; otherwise fails. Example:
?- taylor_contractor({X**4-4*X**3+4*X**2-4*X+3==0},T). T = cf_contractor([X], [_A]), X::real(-1.509169756145379, 4.18727500493995), _A::real(-1.0Inf, 1.0Inf).
Use the contractor with cf_solve
to search for solutions, as in:
?- X::real,taylor_contractor({X**4-4*X**3+4*X**2-4*X+3==0},T), cf_solve(T). T = cf_contractor([X], [_A]), X:: 1.000000000..., _A::real(-1.0Inf, 1.0Inf) ; T = cf_contractor([X], [_A]), X:: 3.00000000..., _A::real(-1.0Inf, 1.0Inf) ; false.
Multiple equality constraints are supported, as in this example of the Broyden banded problem (N=2):
?- taylor_contractor({2*X1+5*X1**3+1==X2*(1+X2), 2*X2+5*X2**3+1==X1*(1+X1)},T), cf_solve(T). T = cf_contractor([X2, X1], [_A, _B]), X1:: -0.42730462..., X2:: -0.42730462..., _B::real(-1.0Inf, 1.0Inf), _A::real(-1.0Inf, 1.0Inf) ; false.
Centre form contractors can converge faster than the general purpose builtin fixed point iteration provided by solve/1
.
==
or =:=
) constraint in Constraints; otherwise fails.
X*C
(or C*X
) are permitted since the actual computation is done using library(simplex)
. Narrowing of minimizers (variables in ObjF) is limited to that constrained by the Min result to accomodate multiple sets of minimizers. (See lin_minimize/3
to use minimizers used to derive Min.) A solution generator, e.g., clpBNR:solve/1
can be used to search for alternative sets of minimizers. "Universal Mines" example from the User Guide:
?- [M_Idays,M_IIdays,M_IIIdays]::integer(0,7), lin_minimum(20*M_Idays+22*M_IIdays+18*M_IIIdays, {4*M_Idays+6*M_IIdays+M_IIIdays>=54,4*M_Idays+4*M_IIdays+6*M_IIIdays>=65}, Min). Min = 284, M_Idays::integer(2, 7), M_IIdays::integer(4, 7), M_IIIdays::integer(2, 7). ?- [M_Idays,M_IIdays,M_IIIdays]::integer(0,7), lin_minimum(20*M_Idays+22*M_IIdays+18*M_IIIdays, {4*M_Idays+6*M_IIdays+M_IIIdays>=54,4*M_Idays+4*M_IIdays+6*M_IIIdays>=65}, Min), solve([M_Idays,M_IIdays,M_IIIdays]). M_Idays = 2, M_IIdays = 7, M_IIIdays = 5, Min = 284 ; false.
For linear systems, lin_minimum/3
, lin_maximum/3
can be significantly faster than using the more general purpose clpBNR:global_minimum/3
, clpBNR:global_maximum/3
lin_minimum/3
for finding global maxima.
lin_minimum/3
except variables in ObjF will be narrowed to the values used in calculating the final value of Min. Any other sets of minimizers corresponding to Min are removed from the solution space. "Universal Mines" example from the User Guide:
?- [M_Idays,M_IIdays,M_IIIdays]::integer(0,7), lin_minimize(20*M_Idays+22*M_IIdays+18*M_IIIdays, {4*M_Idays+6*M_IIdays+M_IIIdays>=54,4*M_Idays+4*M_IIdays+6*M_IIIdays>=65}, Min). M_Idays = 2, M_IIdays = 7, M_IIIdays = 5, Min = 284.
lin_maximum/3
except variables in ObjF will be narrowed to the values used in calculating the final value of Max. Any other sets of minimizers corresponding to Min are removed from the solution space.
local_minima
should be executed prior to a call to clpBNR:global_minimum
using the same objective function, e.g.,
?- X::real(0,10), OF=X**3-6*X**2+9*X+6, local_minima(OF), global_minimum(OF,Z). OF = X**3-6*X**2+9*X+6, X:: 3.00000000000000..., Z:: 6.000000000000... .
Using any local optima predicate can significantly improve performance compared to searching for global optima (clpBNR:global_
*) without local constraints.
local_maxima
should be executed prior to a call to clpBNR:global_maximum
using the same objective function, e.g.,
?- X::real(0,10), OF=X**3-6*X**2+9*X+6, local_maxima(OF), global_maximum(OF,Z). OF = X**3-6*X**2+9*X+6, X:: 1.000000000000000..., Z:: 10.0000000000000... .
local_minima
should be executed prior to a call to clpBNR:global_minimum
using the same objective function, e.g.,
?- [X1,X2]::real, OF=X1**4*exp(-0.01*(X1*X2)**2), local_minima(OF,{2*X1**2+X2**2==10}), global_minimum(OF,Z), solve([X1,X2]). OF = X1**4*exp(-0.01*(X1*X2)**2), X1::real(-1.703183936003284e-108, 1.703183936003284e-108), X2:: -3.16227766016838..., Z:: 0.0000000000000000... ; OF = X1**4*exp(-0.01*(X1*X2)**2), X1::real(-1.703183936003284e-108, 1.703183936003284e-108), X2:: 3.16227766016838..., Z:: 0.0000000000000000... .
local_maxima
should be executed prior to a call to clpBNR:global_maximum
using the same objective function, e.g.,
?- [X1,X2]::real,OF=X1**4*exp(-0.01*(X1*X2)**2), local_maxima(OF,{2*X1**2+X2**2==10}), global_maximum(OF,Z),solve([X1,X2]). OF = X1**4*exp(-0.01*(X1*X2)**2), X1:: -2.23606797749979..., X2:: 0.0000000000000000..., Z:: 25.0000000000000... ; OF = X1**4*exp(-0.01*(X1*X2)**2), X1:: 2.23606797749979..., X2:: 0.0000000000000000..., Z:: 25.0000000000000... .