Stáhnout: 6.3_14.pl  SWISH   Zobrazit: duálně   6.3_14.py

% nacteni:
/* ['6.3_14.pl']. */

:- retractall(write_all_X/3).
:- retractall(start/0).

:- use_module(library(clpfd)). % clpq , clpr

queens(N,L,Type):- length(L,N),
                   L ins 1..N,
                   constr_all(L),
                   labeling(Type,L).
constr_all([]).
constr_all([X|Xs]):- constr_between(X,Xs,1), constr_all(Xs).
constr_between(_,[],_).
constr_between(X,[Y|Ys],N):- no_threat(X,Y,N),
                             N1 is N+1,
                             constr_between(X,Ys,N1).
                             
no_threat(X,Y,J):- X #\= Y, X+J #\= Y, X-J #\= Y.

:- dynamic
       write_all_X/3,
       start/0.
       
write_all_X(Goal,X,Name):-
            call(Goal),write('  '),write(Name),write(' = '),write(X),nl,fail.
write_all_X(_,_,_).

start:- 
    write('CLP - Problem N dam'),nl,nl,
    write('Vysledek dotazu "queens(4, L, [ff])":'),nl,
    write_all_X(queens(4, L, [ff]), L, 'L').
    
?-start.

 Stáhnout: 6.3_14.pl  SWISH   Zobrazit: duálně   6.3_14.py