
(Other examples can be found in the source and library directories.)
:- module(fib_q, [fib/2], []).
:- use_package(clpq).
fib(X,Y):- X .=. 0, Y .=. 0.
fib(X,Y):- X .=. 1, Y .=. 1.
fib(N,F) :-
N .>. 1,
N1 .=. N - 1,
N2 .=. N - 2,
fib(N1, F1),
fib(N2, F2),
F .=. F1+F2.
:- use_package(clpq).
mmultiply([],_,[]).
mmultiply([V0|Rest], V1, [Result|Others]):-
mmultiply(Rest, V1, Others),
multiply(V1,V0,Result).
multiply([],_,[]).
multiply([V0|Rest], V1, [Result|Others]):-
multiply(Rest, V1, Others),
vmul(V0,V1,Result).
vmul([],[],0).
vmul([H1|T1], [H2|T2], Result):-
vmul(T1,T2, Newresult),
Result .=. H1*H2+Newresult.
matrix(1,[[1,2,3,4,5],[4,0,-1,5,6],[7,1,-2,8,9],[-1,0,1,3,2],[1,5,-3,2,4]]).
matrix(2,[[3,2,1,0,-1],[-2,1,3,0,2],[1,2,0,-1,5],[1,3,2,4,5],[-5,1,4,2,2]]).
%% Call with: ?- go(M).
go(M):-
matrix(1,M1),
matrix(2,M2),
mmultiply(M1, M, M2).
:- use_package(clpq).
:- use_module(library(lists), [member/2]).
queens(N, Qs) :- constrain_values(N, N, Qs), place_queens(N, Qs).
constrain_values(0, _N, []).
constrain_values(N, Range, [X|Xs]) :-
N .>. 0, X .>. 0, X .=<. Range,
N1 .=. N - 1,
constrain_values(N1, Range, Xs), no_attack(Xs, X, 1).
no_attack([], _Queen, _Nb).
no_attack([Y|Ys], Queen, Nb) :-
Queen .<>. Y+Nb,
Queen .<>. Y-Nb,
Nb1 .=. Nb + 1,
no_attack(Ys, Queen, Nb1).
place_queens(0, _).
place_queens(N, Q) :-
N > 0, member(N, Q), N1 is N-1, place_queens(N1, Q).
The implementation of CLP(Q) in Ciao compiles the constraints in the program to a sequence of calls to the underlying constraints solver (at compile-time). This results in efficient implementation, since the structure of the constraints is processed only at compile-time, but requires the constraints to be known at static time which can be a limitation for metaprogramming-based applications such as static program analyzers. For example, the call:
?- X=(A+B), Y=(C-D), X .>. Y. no
fails because X .>. Y is translated first to a sequence of calls that require (when they invoked) X and Y to be either numbers or free variables. To overcome this limitation, you can use clpq_meta/1 which delays the translation of the constraints from compile-time to run-time (i.e., when clpq_meta/1 is called), For example:
?- X=(A+B),Y=(C-D), clpq_meta([X .>. Y]). X = A+B, Y = C-D, C.<.D+A+B ?
The argument of clpq_meta/1 accepts a goal or lists of goals, where each goal is limited to conjunctions, disjunctions, or CLP(Q) constraints. Other operations on constraints which are extensively used in meta-programming, in particular in static program analysis, are projection and entailment check. The projection operation restricts the constraints (that are available in the store) to a given set of variables and turns the answer into terms. You can use the multifile predicate dump_constraints/3 for that purpose:
?- A .>. C, C .>. B, dump_constraints([A,B],[X,Y],Cs). Cs = [X.>.Y], C.>.B, C.<.A ? ?- C=(B+D), clpq_meta([A .>. C, D .>. 0]), dump_constraints([A,B],[X,Y],Cs). C = B+D, Cs = [Y.<.X], D.<. -B+A, D.>.0 ?
The entailment check is used to check if a list of constrains is entailed by the store. You can use the predicate clpq_entailed/1 for that purpose:
?- A .>. C, C .>. B, B .>. D, clpq_entailed([ A .>. B, A .>. D]). B.>.D, C.>.B, C.<.A ? yes ?- A .>=. B, clpq_entailed([ A .>. B ]). no