Go to the first, previous, next, last section, table of contents.


Constraint programming over rationals

Author(s): Christian Holzbaur, Daniel Cabeza.

Version: 1.11#222 (2004/5/24, 13:8:7 CEST)

Version of last change: 1.9#184 (2003/12/5, 14:7:53 CET)

Note: This package is currently being adapted to the new characteristics of the Ciao module system. This new version now works right now to some extent, but it is under further development at the moment. Use with (lots of) caution.

Usage and interface (clpq)

Other information (clpq)

Some CLP(Q) examples

(Other examples can be found in the source and library directories.)

:- module(_, [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).
:- use_module(library(write)).

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).

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).

Known bugs and planned improvements (clpq)


Go to the first, previous, next, last section, table of contents.