update to newer version
This commit is contained in:
@@ -1,7 +1,7 @@
|
||||
|
||||
% Coins -- 2007 by Yuce Tekol <yucetekol@gmail.com>
|
||||
|
||||
:- use_module(library('clpfd')).
|
||||
:- use_module(library(clpfd)).
|
||||
|
||||
coins(S, Count, Total) :-
|
||||
% A=1, B=5, C=10, D=50, E=100
|
||||
|
@@ -5,7 +5,7 @@ from pyswip.prolog import Prolog
|
||||
|
||||
def main():
|
||||
prolog = Prolog()
|
||||
|
||||
|
||||
a1 = PL_new_term_refs(2)
|
||||
a2 = a1 + 1
|
||||
t = PL_new_term_ref()
|
||||
@@ -13,6 +13,7 @@ def main():
|
||||
|
||||
animal2 = PL_new_functor(PL_new_atom("animal"), 2)
|
||||
assertz = PL_new_functor(PL_new_atom("assertz"), 1)
|
||||
|
||||
PL_put_atom_chars(a1, "gnu")
|
||||
PL_put_integer(a2, 50)
|
||||
#PL_cons_functor(t, animal2, a1, a2)
|
||||
|
@@ -4,7 +4,7 @@
|
||||
|
||||
solve(Board) :-
|
||||
Board = [NW,N,NE,W,E,SW,S,SE],
|
||||
domains(Board,0..12),
|
||||
maplist(in_board(0..12), Board),
|
||||
sum(Board, #=, 12),
|
||||
NW + N + NE #= 5,
|
||||
NE + E + SE #= 5,
|
||||
@@ -12,7 +12,4 @@ solve(Board) :-
|
||||
SW + S + SE #= 5,
|
||||
label(Board).
|
||||
|
||||
domains([],_).
|
||||
domains([Pos|Board],D) :-
|
||||
Pos in D,
|
||||
domains(Board,D).
|
||||
in_board(D, V) :- V in D.
|
||||
|
@@ -17,9 +17,7 @@ call(assertz(parent("gina", "bob")), module=test2)
|
||||
print "knowledgebase test1"
|
||||
|
||||
X = Variable()
|
||||
print "ok"
|
||||
q = Query(parent(X, "bob"), module=test1)
|
||||
print "ok"
|
||||
while q.nextSolution():
|
||||
print X.value
|
||||
q.closeQuery()
|
||||
|
@@ -2,11 +2,11 @@
|
||||
% SEND + MORE = MONEY
|
||||
% Adapted from: http://en.wikipedia.org/wiki/Constraint_programming
|
||||
|
||||
:- use_module(library(clpfd)).
|
||||
:- use_module(library('bounds')).
|
||||
|
||||
sendmore(Digits) :-
|
||||
Digits = [S,E,N,D,M,O,R,Y], % Create variables
|
||||
allin(Digits, 0..9), % Associate domains to variables
|
||||
Digits in 0..9, % Associate domains to variables
|
||||
S #\= 0, % Constraint: S must be different from 0
|
||||
M #\= 0,
|
||||
all_different(Digits), % all the elements must take different values
|
||||
@@ -15,8 +15,3 @@ sendmore(Digits) :-
|
||||
#= 10000*M + 1000*O + 100*N + 10*E + Y,
|
||||
label(Digits). % Start the search
|
||||
|
||||
|
||||
allin([],_).
|
||||
allin([Pos|Board],D) :-
|
||||
Pos in D,
|
||||
allin(Board,D).
|
||||
|
@@ -8,7 +8,7 @@
|
||||
|
||||
sudoku(Pss) :-
|
||||
flatten(Pss, Ps),
|
||||
allin(Ps, 1..9),
|
||||
maplist(all_in(1..9), Ps),
|
||||
maplist(all_different, Pss),
|
||||
Pss = [R1,R2,R3,R4,R5,R6,R7,R8,R9],
|
||||
columns(R1, R2, R3, R4, R5, R6, R7, R8, R9),
|
||||
@@ -25,7 +25,5 @@ blocks([X1,X2,X3|R1], [X4,X5,X6|R2], [X7,X8,X9|R3]) :-
|
||||
all_different([X1,X2,X3,X4,X5,X6,X7,X8,X9]),
|
||||
blocks(R1, R2, R3).
|
||||
|
||||
allin([],_).
|
||||
allin([Pos|Board],D) :-
|
||||
Pos in D,
|
||||
allin(Board,D).
|
||||
all_in(D, Pos) :-
|
||||
Pos in D.
|
||||
|
Reference in New Issue
Block a user