[ Reference Manual | Alphabetic Index ]

library(gfd)

Interface to gecode solver for integer finite domains   [more]

Predicates

?Vars #:: ++Domain
Constrain Vars to have the domain Domain.
#::(?Var, ++Domain, ?Bool)
Reflect into Bool the truth of Var having the domain Domain.
<ConsistencyModule:> ?ExprX #< ?ExprY
ExprX is less than ExprY.
<ConsistencyModule:> #<(?ExprX, ?ExprY, ?Bool)
Reified ExprX is less than ExprY.
<ConsistencyModule:> ?ExprX #= ?ExprY
ExprX is equal to ExprY.
<ConsistencyModule:> #=(?ExprX, ?ExprY, ?Bool)
Reified ExprX is equal to ExprY.
<ConsistencyModule:> ?ExprX #=< ?ExprY
ExprX is less than or equal to ExprY.
<ConsistencyModule:> #=<(?ExprX, ?ExprY, ?Bool)
Reified ExprX is less than or equal to ExprY.
<ConsistencyModule:> ?ExprX #> ?ExprY
ExprX is strictly greater than ExprY.
<ConsistencyModule:> #>(?ExprX, ?ExprY, ?Bool)
Reified ExprX is strictly greater than ExprY.
<ConsistencyModule:> ?ExprX #>= ?ExprY
ExprX is greater than or equal to ExprY.
<ConsistencyModule:> #>=(?ExprX, ?ExprY, ?Bool)
Reified ExprX is greater than or equal to ExprY.
<ConsistencyModule:> ?ExprX #\= ?ExprY
ExprX is not equal to ExprY.
<ConsistencyModule:> #\=(?ExprX, ?ExprY, ?Bool)
Reified ExprX is not equal to ExprY.
?Vars :: ++Domain
Constrain Vars to have the domain Domain.
::(?Var, ++Domain, ?Bool)
Reflect into Bool the truth of Var having the domain Domain.
<ConsistencyModule:> +ConX <=> +ConY
Constraint ConX has the equivalent truth value as ConY.
<ConsistencyModule:> <=>(+ConX,+ConY,Bool)
Bool is the reified truth of constraint ConX is equivalent to the truth of ConY.
<ConsistencyModule:> +ConX => +ConY
Constraint ConX implies ConY.
<ConsistencyModule:> =>(+ConX,+ConY,Bool)
Bool is the reified truth of constraint ConX implying the truth of ConY.
<ConsistencyModule:> all_eq(?Collection,?Y)
Constrains Collection to be equal to Y.
<ConsistencyModule:> all_ge(?Collection,?Y)
Constrains Collection to be greater than or equal to Y.
<ConsistencyModule:> all_gt(?Collection,?Y)
Constrains Collection to be greater than Y.
<ConsistencyModule:> all_le(?Collection,?Y)
Constrains all in Collection to be less than or equal to Y.
<ConsistencyModule:> all_lt(?Collection,?Y)
Constrains Collection to be less than Y.
<ConsistencyModule:> all_ne(?Collection,?Y)
Constrains Collection to be not equal to Y.
<ConsistencyModule:> alldifferent(+Vars)
All elements of Vars are different.
<ConsistencyModule:> alldifferent_cst(+Vars,++Offsets)
The values of each element plus corresponding offset are pair-wised different.
<ConsistencyModule:> among(+Values, ?Vars, +Rel, ?N)
The number of occurrence (Occ) in Vars of values taken from the set of values specified in Values satisfy the relation Occ Rel N
<ConsistencyModule:> +ConX and +ConY
Constraints ConX and ConY must both be true.
<ConsistencyModule:> and(+ConX,+ConY,Bool)
Bool is the reified truth of both constraints ConX and ConY being true.
<ConsistencyModule:> atleast(?N, +Vars, +V)
Atleast N elements of Vars have the value V.
<ConsistencyModule:> atmost(?N, +Vars, +V)
At most N elements of Vars have the value V.
bin_packing(+Items, ++ItemSizes, +BinLoads)
The one-dimensional bin packing constraint with loads: packing M items into N bins, each bin having a load
bin_packing(+Items, ++ItemSizes, +N, +BinSize)
The one-dimensional bin packing constraint: packing M items into N bins of size BinSize.
bin_packing_g(+Items, ++ItemSizes, +BinLoads)
The one-dimensional bin packing constraint with loads, using native Gecode indexing
bin_packing_md(+Items, ++ItemMDSizes, +BinMDLoads)
The multi-dimensional bin packing constraint with loads: packing M L-Dimensional items into N L-Dimensional bins, each bin having a load in each dimension
bin_packing_md(+Items, ++ItemMDSizes, +N, +BinMDSize)
The multi-dimensional bin packing constraint: packing M L-dimensional items into N L-dimensional bins of size BinMDSize.
<ConsistencyModule:> bool_channeling(?Var, +DomainBools, +Min)
Channel the domain values of Vars to the 0/1 boolean variables in DomainBools
<ConsistencyModule:> circuit(+Succ)
Constrains elements in Succ to form a Hamiltonian circuit.
<ConsistencyModule:> circuit(+Succ,++CostMatrix,?Cost)
Constrains elements in Succ to form a Hamiltonian circuit with cost Cost.
<ConsistencyModule:> circuit(+Succ,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ to form a Hamiltonian circuit with cost Cost.
<ConsistencyModule:> circuit_g(+Succ)
Constrains elements in Succ to form a Hamiltonian circuit, with native Gecode indexing.
<ConsistencyModule:> circuit_g(+Succ,++CostMatrix,?Cost)
Constrains elements in Succ to form a Hamiltonian circuit with cost Cost. This version uses native Gecode indexing.
<ConsistencyModule:> circuit_g(+Succ,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ to form a Hamiltonian circuit with cost Cost, using native Gecode indexing.
<ConsistencyModule:> circuit_offset(+Succ,+Offset)
Constrains elements (offset by Offset) in Succ to form a Hamiltonian circuit.
<ConsistencyModule:> circuit_offset(+Succ,+Offset,++CostMatrix,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian circuit with cost Cost.
<ConsistencyModule:> circuit_offset(+Succ,+Offset,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian circuit with cost Cost.
<ConsistencyModule:> circuit_offset_g(+Succ, +Offset)
Constrains elements (offset by Offset) in Succ to form a Hamiltonian circuit, with native Gecode indexing.
<ConsistencyModule:> circuit_offset_g(+Succ,+Offset,++CostMatrix,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian circuit with cost Cost. This version uses native Gecode indexing.
<ConsistencyModule:> circuit_offset_g(+Succ,+Offset,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian circuit with cost Cost, using native Gecode indexing.
<ConsistencyModule:> count(+Value, ?Vars, +Rel, ?N)
Constrain the number of occurrence of Value in Vars (Occ) to satisfy the relation Occ Rel N
<ConsistencyModule:> count_matches(+Values, ?Vars, +Rel, ?N)
The number of the elements in Vars that match its corresponding value in Values, Matches, satisfies the relation Matches Rel N.
cumulative(+StartTimes, +Durations, +Usages, +ResourceLimit)
Single resource cumulative constraint on scheduling tasks.
cumulative_optional(+StartTimes, +Durations, +Usages, +ResourceLimit, +Scheduled)
Single resource cumulative constraint on scheduling optional tasks.
<ConsistencyModule:> cumulatives(+StartTimes, +Durations, +Heights, +Assigned, +MachineCapacities)
Multi-resource cumulatives constraint on specified tasks.
<ConsistencyModule:> cumulatives_g(+StartTimes, +Durations, +Heights, +Assigned, +MachineCapacities)
Multi-resource cumulatives constraint on specified tasks, using native Gecode indexing.
<ConsistencyModule:> cumulatives_min(+StartTimes, +Durations, +Heights, +Assigned, +MachineConsumptions)
Multi-resource cumulatives constraint on specified tasks with required minimum resource consumptions.
<ConsistencyModule:> cumulatives_min_g(+StartTimes, +Durations, +Heights, +Assigned, +MachineConsumptions)
Multi-resource cumulatives constraint on specified tasks with required minimum resource consumptions, using native Gecode indexing.
disjoint2(+Rectangles)
Constrains the position (and possibly size) of the rectangles in Rectangles so that none overlaps.
disjoint2_optional(+Rectangles)
Constrains the position (and possibly size) of the (possibly optional) rectangles in Rectangles so that none overlaps.
disjunctive(+StartTimes, +Durations)
Constrain the tasks with specified start times and durations to not overlap in time.
disjunctive_optional(+StartTimes, +Durations, +Scheduled)
Constrain the optional tasks with specified start times and durations to not overlap in time.
<ConsistencyModule:> divmod(?X,?Y,?Q,?M)
Constrains Q to X // Y, and M to X rem Y.
<ConsistencyModule:> element(?Index, +Collection, ?Value)
Value is the Index'th element of the integer collection Collection.
<ConsistencyModule:> element_g(?Index, ++List, ?Value)
Value is the Index'th element of the integer list List, with native Gecode indexing.
exclude(?Var, ++Excl)
Exclude the element Excl from the domain of Var.
exclude_range(?Var, ++Lo, ++Hi)
Exclude the elements Lo..Hi from the domain of Var.
<ConsistencyModule:> extensional(+Vars, ++Transitions, +Start, +Finals)
Constrain Vars' solutions to conform to the finite-state automaton specified by Transitions with start state Start and final states Finals.
<ConsistencyModule:> gcc(+Bounds,+Vars)
Constrain the cardinality of each Value according to the specification in Bounds.
get_bounds(?Var, -Lo, -Hi)
Retrieve the current bounds of Var.
get_constraints_number(?Var, -Number)
Returns the number of propagators attached to the gecode variable representing Var.
get_delta(?Var, -Width)
Returns the width of the interval of Var.
get_domain(?Var, -Domain)
Returns a ground representation of the current GFD domain of a variable.
get_domain_as_list(?Var, -DomainList)
List of all the elements in the GFD domain of Var
get_domain_size(?Var, -Size)
Size is the number of integer elements in the GFD domain for Var
get_finite_integer_bounds(?Var, -Lo, -Hi)
Retrieve the current (finite, integral) bounds of Var.
get_integer_bounds(?Var, -Lo, -Hi)
Retrieve the current bounds of Var.
get_max(?Var, -Hi)
Retrieve the current upper bound of Var.
get_median(?Var, -Median)
Returns the median of the domain of the GFD domain variable Var.
get_min(?Var, -Lo)
Retrieve the current lower bound of Var.
get_regret_lwb(?Var, -Regret)
Returns the regret value for the lower bound of Var.
get_regret_upb(?Var, -Regret)
Returns the regret value for the upper bound of Var.
get_weighted_degree(?Var, -WD)
Returns the weighted degree of domain variable Var.
get_weighted_degree_decay(-Decay)
Return the current decay rate for weighted degree.
gfd_get_default(+Parameter, -DefaultValue)
Get the current default value for GFD Parameter.
gfd_maxint(-Var)
Returns the maximum value allowed in gecode's domain.
gfd_minint(-Var)
Returns the minimum value allowed in gecode's domain.
gfd_set_default(+Parameter, +DefaultValue)
Set the default value for GFD Parameter.
gfd_update
Update the parent Gecode space to the current state.
gfd_vars_exclude(+Vars, ++Excl)
Exclude the element Excl from the domains of Vars.
gfd_vars_exclude_domain(+Vars, ?Domain)
Exclude the values specified in Domain from the domains of Vars.
gfd_vars_exclude_range(+Vars, ++Lo, ++Hi)
Exclude the elements Lo..Hi from the domains of Vars.
gfd_vars_impose_bounds(+Vars, ++Lo, ++Hi)
Update (if required) the bounds of Vars.
gfd_vars_impose_domain(+Vars, ?Domain)
Restrict (if required) the domain of Var to the domain specified in Domain
gfd_vars_impose_max(+Vars, ++Bound)
Update (if required) the upper bounds of Vars.
gfd_vars_impose_min(+Vars, ++Bound)
Update (if required) the lower bounds of Vars.
<ConsistencyModule:> ham_path(?Start,?End,+Succ)
Constrains elements in Succ to form a Hamiltonian path from Start to End.
<ConsistencyModule:> ham_path(?Start,?End,+Succ,++CostMatrix,?Cost)
Constrains elements in Succ to form a Hamiltonian path from Start to End with cost Cost.
<ConsistencyModule:> ham_path(?Start,?End,+Succ,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ to form a Hamiltonian path from Start to End with cost Cost.
<ConsistencyModule:> ham_path_g(?Start,?End,+Succ)
Constrains elements in Succ to form a Hamiltonian path from Start to End, with native Gecode indexing.
<ConsistencyModule:> ham_path_g(?Start,?End,+Succ,++CostMatrix,?Cost)
Constrains elements in Succ to form a Hamiltonian path from Start to End with cost Cost. This version uses native Gecode indexing.
<ConsistencyModule:> ham_path_g(?Start,?End,+Succ,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ to form a Hamiltonian path from Start to End, with cost Cost, using native Gecode indexing.
<ConsistencyModule:> ham_path_offset(?Start,?End,+Succ,+Offset)
Constrains elements (offset by Offset) in Succ to form a Hamiltonian path from Start to End.
<ConsistencyModule:> ham_path_offset(?Start,?End,+Succ,+Offset,++CostMatrix,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian path from Start to End with cost Cost.
<ConsistencyModule:> ham_path_offset(?Start,?End,+Succ,+Offset,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian path from Start to End with cost Cost.
<ConsistencyModule:> ham_path_g(?Start,?End,+Succ,+Offset)
Constrains elements (offset by Offset) in Succ to form a Hamiltonian path from Start to End, with native Gecode indexing.
<ConsistencyModule:> ham_path_offset_g(?Start,?End,+Succ,+Offset,++CostMatrix,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian path from Start to End with cost Cost. This version uses native Gecode indexing.
<ConsistencyModule:> ham_path_offset_g(?Start,?End,+Succ,+Offset,++CostMatrix,+ArcCosts,?Cost)
Constrains elements in Succ (offset by Offset) to form a Hamiltonian path from Start to End with cost Cost, using native Gecode indexing.
impose_bounds(?Var, ++Lo, ++Hi)
Update (if required) the bounds of Var.
impose_domain(?Var, ?DomVar)
Restrict (if required) the domain of Var to the domain of DomVar.
impose_max(?Var, ++Bound)
Update (if required) the upper bound of Var.
impose_min(?Var, ++Bound)
Update (if required) the lower bound of Var.
indomain(?Var)
Instantiates a domain GFD variable to an element of its domain.
integers(?Vars)
Vars' domain is the integer numbers (within default bounds).
<ConsistencyModule:> inverse(+Succ,+Pred)
Constrains elements of Succ to be the successors and Pred to be the predecessors of nodes in a digraph
<ConsistencyModule:> inverse(+Succ,+SuccOffset,+Pred,+PredOffset)
Constrains elements of Succ (with SuccOffset) to be the successors and Pred (with PredOffset) to be the predecessors of nodes in a digraph
<ConsistencyModule:> inverse_g(+Succ,+Pred)
Constrains elements of Succ to be the successors and Pred to be the predecessors of nodes in a digraph, using native Gecode indexing.
<ConsistencyModule:> inverse_g(+Succ,+SuccOffset,+Pred,+PredOffset)
Constrains elements of Succ (with SuccOffset) to be the successors and Pred (with PredOffset) to be the predecessors of nodes in a digraph
is_exact_solver_var(?Term)
Succeeds iff Term is an GFD domain variable.
is_in_domain(++Val, ?Var)
Succeeds iff Val is in the domain of Var
is_in_domain(++Val, ?Var, -Result)
Binds Result to indicate presence of Val in domain of Var
is_solver_type(?Term)
Succeeds iff Term is a GFD domain variable or an integer.
is_solver_var(?Term)
Succeeds iff Term is an GFD domain variable.
labeling(+Vars)
Instantiates all variables in a collection to elements of their domains.
lex_eq(+Collection1, +Collection2)
Collection1 is lexicographically equal to Collection2
lex_ge(+Collection1, +Collection2)
Collection1 is lexicographically greater or equal to Collection2
lex_gt(+Collection1, +Collection2)
Collection1 is lexicographically greater than Collection2
lex_le(+Collection1, +Collection2)
Collection1 is lexicographically less or equal to Collection2
lex_lt(+Collection1, +Collection2)
Collection1 is lexicographically less than Collection2
lex_ne(+Collection1, +Collection2)
Collection1 is lexicographically not equal to Collection2
<ConsistencyModule:> max(+Collection,?Max)
Max is the maximum of the values in Collection
max_first_index(+Collection,?Index)
Index is constrained to the index of the first variable with the maximum value in Collection
max_first_index_g(+Collection,?Index)
Index is constrained to the index of the first variable with the maximum value in Collection, with native gecode indexing
<ConsistencyModule:> max_index(+Collection,?Index)
Index is constrained to the index(es) of the variable(s) with the maximum value in Collection
<ConsistencyModule:> max_index_g(+Collection,?Index)
Index is constrained to the index(es) of the variable(s) with the maximum value in Collection, with native gecode indexing
max_regret_lwb(?Var, ?Criterion)
Generic search compatible variable selection method, returns the regret value for Var
max_regret_upb(?Var, ?Criterion)
Generic search compatible variable selection method, returns the upper-bound regret value for Var
max_weighted_degree(?Var, ?Criterion)
Generic search compatible variable selection method, returns the weighted degree for Var
max_weighted_degree_per_value(?Var, ?Criterion)
Generic search compatible variable selection method, returns the domain size divided by weighted degree for Var
<ConsistencyModule:> mem(+Vars,?Member)
Constrains Member to be the a member element in Vars.
<ConsistencyModule:> mem(+Vars,?Member,?Bool)
Reflect into Bool the truth of Member being a member element of Vars.
<ConsistencyModule:> min(+Collection,?Min)
Min is the minimum of the values in Collection
min_first_index(+Collection,?Index)
Index is constrained to the index of the first variable with the minimum value in Collection
min_first_index_g(+Collection,?Index)
Index is constrained to the index of the first variable with the minimum value in Collection, with native gecode indexing
<ConsistencyModule:> min_index(+Collection,?Index)
Index is constrained to the index(es) of the variable(s) with the minimum value in Collection
<ConsistencyModule:> min_index_g(+Collection,?Index)
Index is constrained to the index(es) of the variable(s) with the minimum value in Collection, with native gecode indexing
most_constrained_per_value(?Var, ?Criterion)
Generic search compatible variable selection method,
msg(?Var1, ?Var2, ?MSG)
Computes the most specific generalisation of Var1 and Var2 that is expressible with GFD variables.
<ConsistencyModule:> neg(+Con)
Constraints Con is negated.
<ConsistencyModule:> neg(+Con,Bool)
Bool is the logical negation of the reified truth constraints Con.
nvalues(+Collection, +RelOp, ?Limit)
Constrains N, the number of distinct values assigned to Collection to satisfy the relation N Rel Limit.
<ConsistencyModule:> occurrences(++Value,+Vars,?N)
The value Value occurs in Vars N times
<ConsistencyModule:> +ConX or +ConY
At least one of the constraints ConX or ConY must be true.
<ConsistencyModule:> or(+ConX,+ConY,Bool)
Bool is the reified truth of at least one of the constraints ConX or ConY being true.
<ConsistencyModule:> ordered(+Relation,+Vars)
Constrains Vars to be ordered according to Relation
precede(++Values, +Collection)
Constrains each value in Values to precede its succeeding value in Collection
precede(+S, +T, +Collection)
Constrains S to precede T in Collection
<ConsistencyModule:> regular(+Vars, ++RegExp)
Constrain Vars' solutions to conform to that defined in the regular expression RegExp.
<ConsistencyModule:> scalar_product(++Coeffs,+Collection,+Rel,?Sum)
Constrains the scalar product of the elements of Coeffs and Collection to satisfy the relation sum(Coeffs*Collection) Rel P.
<ConsistencyModule:> scalar_product(++Coeffs,+Collection,+Rel,?Sum,?Bool)
Reflect into Bool the truth of the scalar product of the elements of Coeffs and Collection satisfying the relation sum(Coeffs*Collection) Rel Sum.
search(+L, ++Arg, ++Select, +Choice, ++Method, +Option)
Interface to gecode search-engines to perform search in gecode.
select_var(-X, +Vars, +Handle, +Arg, ?Select)
Pick a domain variable from a collection according to selection criterion.
<ConsistencyModule:> sequence(+Low,+High,+K,+ZeroOnes)
The number of occurrences of the value 1 is between Low and High for all sequences of K variables in ZeroOnes
<ConsistencyModule:> sequence(+Low,+High,+K,+Vars,++Values)
The number of values taken from Values is between Low and High for all sequences of K variables in Vars.
set_weighted_degree_decay(+Decay)
Change the current decay rate for weighted degree to Decay.
solver_constraints_number(-NumberOfConstraints)
Returns the number of constraints in the gecode solver state
solver_vars_number(-NumberOfVariables)
Returns the number of domain variables in the gecode solver state
<ConsistencyModule:> sorted(?Unsorted, ?Sorted)
Sorted is a sorted permutation of Unsorted
<ConsistencyModule:> sorted(?Unsorted, ?Sorted, ?Positions)
Sorted is a sorted permutation (described by Positions) of Unsorted
<ConsistencyModule:> sorted_g(?Unsorted, ?Sorted, ?Positions)
Sorted is a sorted permutation (described by Positions) of Unsorted, with native Gecode indexing.
<ConsistencyModule:> sum(+Collection,?Sum)
The sum (Collection) or scalar product (IntCollection*Collection) of the Collection elements is Sum
<ConsistencyModule:> sum(+Collection,+Rel,?Sum)
Constrains the sum of the elements of Collection to satisfy the relation sum(Collection) Rel Sum.
<ConsistencyModule:> sum(+Collection,+Rel,?Sum,?Bool)
Reflect into Bool the truth of the sum of the elements of Collection satisfying the relation sum(Collection) Rel Sum.
<ConsistencyModule:> sumlist(+Collection,?Sum)
The sum (Collection) or scalar product (IntCollection*Collection) of the Collection elements is Sum
<ConsistencyModule:> table(+Vars, ++Table)
Constrain Vars' solutions to be those defined by the tuples in Table.
try_value(?Var, ++Method)
Two-way and multi-way choice predicate
<ConsistencyModule:> +ConX xor +ConY
One of the constraints ConX or ConY must be true.
<ConsistencyModule:> xor(+ConX,+ConY,Bool)
Bool is the reified truth of one of the constraints ConX or ConY being true.

Structures

struct gcc(low, high, value)
Bounds specification for gcc constraint.
struct gfd(idx, bool, prob, any, set)
Attribute for gfd domain variable (for implementation use only)
struct gfd_control(commit_distance, adaptive_distance, threads)
Structure for passing low-level control parameters to gecode search-engines.
struct gfd_prob(cp_stamp, nvars, nevents, vars, prop, last_anc, space, events, events_tail)
ECLiPSe level problem handle (for implementation use only)
struct gfd_space(handle, stamp)
Handle for Gecode solver state (for implementation use only)
struct gfd_stats(prop, fail, nodes, depth, mem)
Structure for obtaining statistics or providing stopping limits for gecode search-engines
struct occ(occ, value)
Bounds specification for gcc constraint.
struct rect(x, y, w, h, b)
Specification for rectangles used in disjoint2 and disjoint2_optional constraints.
struct trans(f, t, l)
Specification of s transition in the DFA for extensional/4.

Other Exports

export op(700, xfx, [#::])
export op(750, fx, [neg])
export op(760, yfx, [and])
export op(770, yfx, [or, xor])
export op(790, yfx, [<=>])
export op(780, yfx, [=>])
export portray(gfd_prob / 9, gfd_handle_tr_out / 2, [])

Description

The GFD library is an interface to the gecode finite domain constraint solver. Gecode (www.gecode.org) is an open-source toolkit for developing constraint-based systems in C++, and includes a high-performance constraint solver.

This interface provides a high degree of compatibility with the finite domain portion of the IC library, and to a lesser extent, with the FD library as well. This means that programs originally written for the IC library should run with GFD with little modifications, beyond renaming any explicit calls to the ic family of modules.

The main differences from the IC library are:

The following can be used inside arithmetic integer expressions:

X
Variables. If X is not yet a domain variable, it is turned into one.
123
Integer constants.
-Expr
Sign change.
abs(Expr)
The absolute value of Expr.
E1+E2
Addition.
E1-E2
Subtraction.
E1*E2
Multiplication.
E1//E2
Integer division. Truncate towards zero.
E1/E2
Division, defined only where E2 evenly divides E1 (non-inlined),
E1 rem E2
Integer remainder (modulus), same sign as E1.
Expr^N
Power, Expr to the power N. N is a non-negative integer. Mapped to sqr(Expr) if N = 2.
min(E1,E2)
Minimum.
max(E1,E2)
Maximum.
sqr(Expr)
Square. Logically equivalent to Expr*Expr.
isqrt(Expr)
Integer square root. Truncated to nearest smaller integer. Always non-negative
sqrt(Expr)
Square root, defined only where Expr is the square of an integer. Always non-negative (non-inlined).
inroot(Expr,N)
Integer Nth root. N is a positive integer. Truncated to nearest smaller integer. For even N, result is the non-negative root.
rsqr(Expr)
Reverse of the sqr function. Negative root is not excluded (non-inlined).
rpow(E1,N)
Reverse of exponentiation. i.e. finds X in E1 = X^N. N is a positive integer (non-inlined).
sum(ExprCol)
Sum of a collection of expressions.
sum(IntCol*ExprCol)
Scalar product of a collection of integers and expressions. IntCol and ExprCol must be the same size.
min(ExprCol)
Minimum of a collection of expressions.
max(ExprCol)
Maximum of a collection of expressions.
element(ExprIdx, Col)
Element constraint, Evaluate to the ExprIdx'th element of Col. ExprIdx can be an integer expression.
Functional/reified constraints
Written without last argument, which is taken as the value of the expression. Only reified constraints (whose last argument is the 0/1 boolean) and constraints that can be written as functions (last argument is a domain variable) are allowed. Expressions in relational constraints are restricted to inlined expressions only. (non-inlined).
eval(Expr)
Equivalent to Expr.
ConLev: Expr
Expr is passed to Gecode at constraint level ConLev. ConLev can be gfd_gac, gfd_bc, gfd_vc, gfd.

The following can be used inside logical constraint expressions:

X
Boolean variables with 0..1 domain. If X is not yet a domain variable, it is turned into one.
1
boolean constants. 0 for false, 1 for true.
E1 and E2
Reified constraint conjunction. E1 and E2 are logical constraint expressions.
E1 or E2
Reified constraint disjunction. E1 and E2 are logical constraint expressions.
E1 xor E2
Reified constraint exclusive disjunction/non-equivalence. E1 and E2 are logical constraint expressions.
E1 => E2
Reified constraint implication. E1 and E2 are logical constraint expressions.
E1 <=> E2
Reified constraint equivalence. E1 and E2 are logical constraint expressions.
neg E
Reified constraint negation. E is a logical constraint expression.
element(ExprIdx, BoolCol)
Element constraint, Evaluate to the ExprIdx'th element of BoolCol. ExprIdx can be an inlined integer expression. BoolCol is a collection of boolean values or domain variable.
Reified constraints
Written without last argument, which is taken as the truth value of the expression. Reified relational constraints are supported inlined and only inlined integer expressions are allowed. (non-inlined except reified relational constraints).
eval(Expr)
Equivalent to Expr.
ConLev: Expr
Expr is passed to Gecode at constraint level ConLev. ConLev can be gfd_gac, gfd_bc, gfd_vc, gfd.

About


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