[ Reference Manual | Alphabetic Index ]

library(eplex)

Interface to external Simplex or MIP solvers   [more]

Predicates

?Vars $:: ++Lo..Hi, EplexInstance: (?Vars $:: ++Lo..Hi)
Constrains all collection elements to lie between the given bounds.
?X $= ?Y, EplexInstance:(?X $= ?Y)
Constrains X to be equal to Y.
?X $=< ?Y, EplexInstance:(?X $=< ?Y)
Constrains X to be less than or equal to Y.
?X $>= ?Y, EplexInstance:(?X $>= ?Y)
Constrains X to be greater than or equal to Y.
Ind => LinCon, EplexInstance:(Ind => LinCon)
Linear constraint conditional on binary variable
eplex_add_constraints(+Constraints,+Integers), EplexInstance: eplex_add_constraints(+Constraints,+Integers)
Add new constraints to the eplex instance EplexInstance, possibly triggering it.
eplex_cleanup, EplexInstance:eplex_cleanup
Destroy the external solver associated with EplexInstance.
eplex_get(++ParamName, -Value), EplexInstance:eplex_get(++ParamName, -Value)
Retrieve information about solver state and results for eplex instance EplexInstance.
eplex_get_iis(-NumConstraints, -NumVars, -ConstraintIdxs, -VarInfos), EplexInstance:eplex_get_iis(-NumConstraints, -NumVars, -ConstraintIdxs, -VarInfos)
Returns an IIS for an infeasible problem associated with EplexInstance.
eplex_instance(++EplexInstance)
Initialises the eplex instance EplexInstance.
eplex_probe(+Probes, -Cost), EplexInstance:eplex_probe(+Probes, -Cost)
Invoke EplexInstance's external solver, probing the problem temporarily modified by the probe specifications.
eplex_read(++Format,++File), EplexInstance:eplex_read(++Format,++File)
Read a problem from a file into eplex instance EplexInstance.
eplex_set(++ParamName, -Value), EplexInstance:eplex_set(++ParamName, -Value)
Change initial options for solver state associated with EplexInstance
eplex_solve(-Cost), EplexInstance:eplex_solve(-Cost)
Explicitly invoke the external solver associated with EplexInstance.
eplex_solver_setup(+Objective), EplexInstance:eplex_solver_setup(+Objective)
Setup an external solver state for eplex instance EplexInstance
eplex_solver_setup(+Objective, ?Cost, ++ListOfOptions, +TriggerModes), EplexInstance:eplex_solver_setup(+Objective, ?Cost, ++ListOfOptions, +TriggerModes)
Setup an external solver state for eplex instance EplexInstance
eplex_var_get(+Var, ++What, -Value), EplexInstance:eplex_var_get(+Var, ++What, -Value)
Obtain information for an individual solver problem variable Var.
eplex_var_get_bounds(+Var, -Lo, -Hi), EplexInstance:eplex_var_get_bounds(+Var, -Lo, -Hi)
Returns the bounds stored in the solver state for Var in eplex instance EplexInstance.
eplex_verify_solution(-ViolatedCstrs,-ViolatedVars), EplexInstance:eplex_verify_solution(-ViolatedCstrs,-ViolatedVars)
Verifies the current solution for the problem associated with EplexInstance.
eplex_write(++Format,++File), EplexInstance:eplex_write(++Format,++File)
Write the problem in the solver for eplex instance EplexInstance to a file.
get_changeable_value(?Var, -Val), EplexInstance:get_changeable_value(?Var, -Val)
Interface predicate to access the `changeable' value for this variable.
instantiation_deviates(+Handle)
A trigger goal for lp_demon_setup/5.
integers(?Vars), EplexInstance:integers(?Vars)
Constrains Vars to integers for eplex instance EplexInstance.
lp_add(+Handle, +NewNormCons, +NewIntegers)
Add new constraints to a solver state Handle.
lp_add_columns(+Handle, +Columns)
Add new variables as columns to the external solver's matrix.
lp_add_constraints(+Handle, +Constraints, ++Integers)
Add new constraints to the solver Handle, possibly triggering it.
lp_add_constraints(+Handle, +Constraints, ++Integers, -Indices)
Add new expandable constraints to the demon solver Handle.
lp_add_cutpool_constraints(+Handle, +Constraints, +Options, -Indices)
Add constraints to the cutpool associated with solver state Handle.
lp_add_vars(+Handle, +Vars)
Declare Vars to be problem variables for the solver state Handle
lp_cleanup(+Handle)
Destroy the specified solver Handle and clean up.
lp_demon_setup(+Objective, ?Cost, ++ListOfOptions, ++TriggerModes, -Handle)
Setup the external solver as a simplex demon.
lp_get(++ParamName, ?Value)
Obtain the value of a global parameter.
lp_get(+Handle, ++ParamName, -Value)
Retrieve information about solver state and results for solver state Handle.
lp_get_changeable_value(+Handle, ?Var, -Val)
Interface predicate to access the `changeable' value for this variable.
lp_get_iis(+Handle, -NumConstraints, -NumVars, -ConstraintIdxs, -VarInfos)
Returns an IIS for an infeasible problem.
lp_get_license
Get a runtime license token for the external solver.
lp_get_license(+LicStr, +LicNum)
Get a runtime license token for the external solver.
lp_get_license_challenge(-Challenge)
Get parameter for computing license key (some external solvers only)
lp_probe(+Handle, +Probes, -Cost)
Invoke external solver, probing the problem temporarily modified by the probe specifications.
lp_read(+File, ++Format, -Handle)
Read a problem from a file and setup a solver for it.
lp_release_license
Release a runtime license token for the external solver.
lp_set(++ParamName, ++Value)
Set a global parameter for the external solver.
lp_set(+Handle, ++What, +Value)
Change initial options for solver state Handle.
lp_setup(+NormConstraints, +Objective, ++ListOfOptions, -Handle)
Create a new external solver state for the constraints NormConstraints.
lp_solve(+Handle, -Cost)
Explicitly invoke the external solver.
lp_suspend_on_change(+Handle, ?Var, +Susp)
Record the given suspension to be scheduled whenever a solution is found for the Eplex handle.
lp_var_get(+Handle, +Var, ++What, -Value)
Obtain information for an individual solver problem variable Var.
lp_var_get_bounds(+Handle, ?Var, -Lo, -Hi)
Returns the bounds stored in the solver state of Handle for Var.
lp_var_occurrence(?Var, ?Handle, -Index)
Returns the column number Index for Var in the external solver represented by Handle
lp_var_set_bounds(+Handle, ?Var, +Lo, +Hi)
Imposes new bounds for Var on the solver state of Handle.
lp_verify_solution(+Handle, -ViolatedCstrs, -ViolatedVars)
Verifies the current solution for the problem associated with Handle.
lp_write(+Handle, ++Format, +File)
Write a solver problem to a file.
normalise_cstrs(+Constraints, -NormConstraints, -NonlinConstraints)
Normalise the linear constraints in Constraints.
optimize(+Objective, -Cost), EplexInstance:optimize(+Objective, -Cost)
Setup problem, solve and instantiate problem variables
optimize(+Objective, -Cost, +Options), EplexInstance:optimize(+Objective, -Cost, +Options)
Setup problem, solve and instantiate problem variables
piecewise_linear_hull(?X, ++Points, ?Y), EplexInstance:piecewise_linear_hull(?X, ++Points, ?Y)
Relates X and Y according to a piecewise linear function.
reals(?Vars), EplexInstance:reals(?Vars)
Constraints Vars to the real domain for EplexInstance.
reduced_cost_pruning(+Handle, ?GlobalCost)
Prune bounds of all problem variables based on their reduced costs
solution_out_of_range(+Handle)
A trigger goal for lp_demon_setup/5.
sos1(?Vars), EplexInstance:sos1(?Vars)
Constrains all but one of Vars to be zero.
sos2(?Vars), EplexInstance:sos2(?Vars)
Constrains all but two consecutive elements of Vars to be zero.
suspend_on_change(?Var, +Susp), EplexInstance:suspend_on_change(?Var, +Susp)
Record the given suspension to be scheduled whenever a solution is found for the EplexInstance.

Reexports

reexport eplex_
except add_constraint / 1, lp_eq / 3, lp_ge / 3, lp_le / 3, lp_interval / 3, reals / 2, integers / 2, optimize_pool / 3, optimize_pool_body / 4, optimize_pool / 4, optimize_pool_body / 5, suspend_on_change / 3, get_changeable_value / 3, lp_var_non_monotonic_set_bounds / 4, piecewise_linear_hull / 4, eplex_add_constraints / 3, eplex_get / 3, eplex_cleanup / 1, eplex_probe / 3, eplex_solve / 2, eplex_solver_setup / 2, eplex_solver_setup_cbody / 5, eplex_solver_setup_cbody / 6, eplex_var_get / 4, eplex_var_get_bounds / 4, eplex_set / 3, eplex_read / 3, eplex_verify_solution / 3, eplex_write / 3, eplex_get_iis / 5

Description

This library lets you use an external Mathematical Programming solver from within ECLiPSe. Solver that can be connected through eplex include

For the commercial solvers, this library provides just the interface, and does not include the solver or any required licence to use them.

The constraints provided are:

reals(Xs)
the variables Xs all take real values
integers(Xs)
the variables Xs all take integer values
Xs $:: Lwb..Upb
the variables Xs have the given bounds
X $= Y
equality over linear expressions
X $>= Y
inequality over linear expressions
X $=< Y
inequality over linear expressions
Depending on the capabilities of the external solver, the following may also be supported:
sos1(Xs)
all but one are zero
sos2(Xs)
all but two consecutive values are zero
Cond=>Linear
indicator constraint (some solvers only)
The operational behaviour of the linear constraints is as follows:

The following arithmetic expression can be used inside the constraints:

X
Variables. If X is not yet a problem variable for the external solver instance, it is turned into one via an implicit declaration X $:: -inf..inf or reals([X]).

123, 3.4
Integer or floating point constants.

+Expr
Identity.

-Expr
Negation.

E1+E2
Addition.

E1-E2
Subtraction.

E1*E2
Multiplication.

sum(Vector)
Equivalent to the sum of all vector elements. The vector can be a list, array or any of the vector expressions supported by eval_to_list/2.

sum(Vector1*Vector2)
Scalar product: The sum of the products of the corresponding elements in the two vectors. The vectors can be lists, arrays or any of the vector expressions supported by eval_to_list/2. If the vectors are of different length, the shorter one is padded with trailing zeros.

The external solver can either be explicitly invoked to solve the problem represented by the constraints, or be invoked in response to certain trigger conditions. This mechanism makes it possible to tailor the solving behaviour for a particular application's needs.

Examples

    % Linear Programming example: transport problem

    :- lib(eplex).

    main(Cost, Supply) :-
        data(PlantCapacities, ClientDemands, TranspCosts),
        dim(TranspCosts, [NClients,NPlants]),   % get dimensions

        dim(Supply, [NClients,NPlants]),        % make variables
        Supply :: 0.0..inf,                     % initial bounds

        ( for(J,1,NClients), param(ClientDemands,Supply) do
            sum(Supply[J,*]) $= ClientDemands[J]
        ),

        ( for(I,1,NPlants), param(PlantCapacities,Supply) do
            sum(Supply[*,I]) $=< PlantCapacities[I]
        ),

        Objective = sum(concat(TranspCosts)*concat(Supply)),

        optimize(min(Objective), Cost).         % solve

    data(
        [](500, 300, 400),              % PlantCapacities
        [](200, 400, 300, 100),         % ClientDemands
        []([](10, 7, 11),               % TranspCosts
           []( 8, 5, 10),
           []( 5, 5,  8),
           []( 9, 3,  7))
    ).


    % Sample run

    ?- main(Cost, Supply).
    Cost = 6600.0
    Supply = []([](100.0, 0.0, 100.0),
                [](100.0, 300.0, 0.0),
                [](300.0, 0.0, 0.0),
                [](0.0, 0.0, 100.0))
    Yes (0.00s cpu)

About


Generated from eplex.eci on 2022-09-03 14:26