Constraint programming over finite domains

Author(s): José Manuel Gómez Pérez, Manuel Carro.

This package is not anymore maintained. Prefer package clpfd which provides similar features.

This package is a very preliminary implementation of a finite domain solver. Examples can be found in the source and library directories.

  • SEND + MORE = MONEY:

:- use_package(fd).
:- use_module(library(prolog_sys), [statistics/2]).
:- use_module(library(format)).


smm(SMM) :-
	statistics(runtime,_),
	do_smm(SMM),
	statistics(runtime,[_, Time]),
	format("Used ~d milliseconds~n", Time).

do_smm(X) :-
	X = [S,E,N,D,M,O,R,Y],
	X in 0 .. 9,
	all_different(X),
	M .>. 0,
	S .>. 0,
	1000*S + 100*E + 10*N + D + 1000*M + 100*O + 10*R + E
        .=. 10000*M + 1000*O + 100*N + 10*E + Y,
	labeling(X).

  • Queens:

:- use_package(fd).
:- use_module(library(prolog_sys), [statistics/2]).
:- use_module(library(format)).
:- use_module(library(aggregates)).
:- use_module(library(lists), [length/2]).


queens(N, Qs) :-
	statistics(runtime,_),
	do_queens(N, Qs),
	statistics(runtime,[_, Time]),
	format("Used ~d milliseconds~n", Time).

do_queens(N, Qs):- 
	constrain_values(N, N, Qs),
	all_different(Qs),!,
	labeling(Qs).

constrain_values(0, _N, []).
constrain_values(N, Range, [X|Xs]):-
        N > 0, 
        X in 1 .. Range,
        N1 is N - 1,
        constrain_values(N1, Range, Xs),
        no_attack(Xs, X, 1).

no_attack([], _Queen, _Nb).
no_attack([Y|Ys], Queen, Nb):-
	Nb1 is Nb + 1,
	no_attack(Ys, Queen, Nb1),
	Queen .<>. Y + Nb,
	Queen .<>. Y - Nb.	


Usage and interface

Documentation on exports

REGTYPE

Usage:fd_item(FD_item)

FD_item is a finite domain entity, i.e. either a finite domains variable or an integer.

    REGTYPE

    Usage:fd_range(FD_range)

    FD_range is the range of a finite domain entity.

      REGTYPE

      Usage:

      A subrange is a pair representing a single interval.

        REGTYPE

        Usage:fd_store(FD_store)

        FD_store is a representation of the constraint store of a finite domain entity.

          REGTYPE

          Usage:

          Representation of primitive constraints.

            PREDICATE

            Usage:labeling(Vars)

            Implements the labeling process. Assigns values to the input variables Vars. On exit all variables are instantiated to a consistent value. On backtracking, the predicate returns all possible assignments. No labeling heuristics implemented so far, i.e. variables are instantiated in their order of appearance.

            • The following properties should hold at call time:
              (basic_props:list/2)Vars is a list of fd_items.

            PREDICATE

            Usage:pitm(V,MiddlePoint)

            Returns in MiddlePoint the intermediate value of the range of V. In case V is a ground integer value the returned value is V itself.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)V is currently a term which is not a free variable.
              (term_typing:var/1)MiddlePoint is a free variable.
              (user(... /fd_doc):fd_item/1)V is a finite domain entity, i.e. either a finite domains variable or an integer.
              (basic_props:int/1)MiddlePoint is an integer.

            PREDICATE

            Usage:choose_var(ListOfVars,Var,RestOfVars)

            Returns a finite domain item Var from a list of fd items ListOfVars and the rest of the list RestOfVarsin a deterministic way. Currently it always returns the first item of the list.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)ListOfVars is currently a term which is not a free variable.
              (term_typing:var/1)Var is a free variable.
              (term_typing:var/1)RestOfVars is a free variable.
              (basic_props:list/2)ListOfVars is a list of fd_items.
              (user(... /fd_doc):fd_item/1)Var is a finite domain entity, i.e. either a finite domains variable or an integer.
              (basic_props:list/2)RestOfVars is a list of fd_items.

            PREDICATE

            Usage:choose_free_var(ListOfVars,Var)

            Returns a free variable Var from a list of fd items ListOfVars. Currently it always returns the first free variable of the list.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)ListOfVars is currently a term which is not a free variable.
              (term_typing:var/1)Var is a free variable.
              (basic_props:list/2)ListOfVars is a list of fd_items.
              (term_typing:var/1)Var is a free variable.

            PREDICATE

            Usage:choose_var_nd(ListOfVars,Var)

            Returns non deterministically an fd item Var from a list of fd items ListOfVars .

            • The following properties should hold at call time:
              (term_typing:nonvar/1)ListOfVars is currently a term which is not a free variable.
              (term_typing:var/1)Var is a free variable.
              (basic_props:list/2)ListOfVars is a list of fd_items.
              (user(... /fd_doc):fd_item/1)Var is a finite domain entity, i.e. either a finite domains variable or an integer.

            PREDICATE

            Usage:choose_value(Var,Value)

            Produces an integer value Value from the domain of Var. On backtracking returns all possible values for Var.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)Var is currently a term which is not a free variable.
              (term_typing:var/1)Value is a free variable.
              (user(... /fd_doc):fd_item/1)Var is a finite domain entity, i.e. either a finite domains variable or an integer.
              (basic_props:int/1)Value is an integer.

            PREDICATE

            Usage:retrieve_range(Var,Range)

            Returns in Range the range of an fd item Var.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)Var is currently a term which is not a free variable.
              (term_typing:var/1)Range is a free variable.
              (term_typing:var/1)Var is a free variable.
              (user(... /fd_doc):fd_range/1)Range is the range of a finite domain entity.

            PREDICATE

            Usage:retrieve_store(Var,Store)

            Returns in Store a representation of the constraint store of an fd item Var.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)Var is currently a term which is not a free variable.
              (term_typing:var/1)Store is a free variable.
              (term_typing:var/1)Var is a free variable.
              (user(... /fd_doc):fd_store/1)Store is a representation of the constraint store of a finite domain entity.

            PREDICATE

            Usage:glb(Var,LowerBound)

            Returns in LowerBound the lower bound of the range of Var.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)Var is currently a term which is not a free variable.
              (term_typing:var/1)LowerBound is a free variable.
              (user(... /fd_doc):fd_item/1)Var is a finite domain entity, i.e. either a finite domains variable or an integer.
              (basic_props:int/1)LowerBound is an integer.

            PREDICATE

            Usage:lub(Var,UpperBound)

            Returns in UpperBound the upper bound of the range of Var.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)Var is currently a term which is not a free variable.
              (term_typing:var/1)UpperBound is a free variable.
              (user(... /fd_doc):fd_item/1)Var is a finite domain entity, i.e. either a finite domains variable or an integer.
              (basic_props:int/1)UpperBound is an integer.

            PREDICATE

            Usage:bounds(Var,LowerBound,UpperBound)

            Returns in LowerBound and UpperBound the lower and upper bounds of the range of Var.

            • The following properties should hold at call time:
              (term_typing:nonvar/1)Var is currently a term which is not a free variable.
              (term_typing:var/1)LowerBound is a free variable.
              (term_typing:var/1)UpperBound is a free variable.
              (user(... /fd_doc):fd_item/1)Var is a finite domain entity, i.e. either a finite domains variable or an integer.
              (basic_props:int/1)LowerBound is an integer.
              (basic_props:int/1)UpperBound is an integer.

            PREDICATE

            Usage:retrieve_list_of_values(Var,ListOfValues)

            Returns in ListOfValues an enumeration of al the values in the range of Var

            • The following properties should hold at call time:
              (term_typing:nonvar/1)Var is currently a term which is not a free variable.
              (term_typing:var/1)ListOfValues is a free variable.
              (user(... /fd_doc):fd_item/1)Var is a finite domain entity, i.e. either a finite domains variable or an integer.
              (basic_props:list/2)ListOfValues is a list of ints.