Minor cleanup.

This commit is contained in:
Simon Forman 2019-11-07 07:55:01 -08:00
parent 3751107a09
commit 53ef16bee4
2 changed files with 12 additions and 5 deletions

View File

@ -61,7 +61,6 @@ next(PC, I) :- PC \= done, relly(PC, I, PCnext, Inext), next(PCnext, Inext).
type_ok(Small, Big) :- Small in 0..3, Big in 0..5. type_ok(Small, Big) :- Small in 0..3, Big in 0..5.
next_dh(Moves) :- next_dh(0, 0, Moves). next_dh(Moves) :- next_dh(0, 0, Moves).
next_dh(Small, Big, [[Move, Si, Bi]|Moves]) :- next_dh(Small, Big, [[Move, Si, Bi]|Moves]) :-
@ -69,7 +68,6 @@ next_dh(Small, Big, [[Move, Si, Bi]|Moves]) :-
die_hard(Move, Small, Big, Si, Bi), die_hard(Move, Small, Big, Si, Bi),
(Bi = 4 -> Moves = [] ; next_dh(Si, Bi, Moves)). (Bi = 4 -> Moves = [] ; next_dh(Si, Bi, Moves)).
die_hard( fill_small, Small, Big, 3, Big) :- Small #< 3. die_hard( fill_small, Small, Big, 3, Big) :- Small #< 3.
die_hard( fill_big, Small, Big, Small, 5) :- Big #< 5. die_hard( fill_big, Small, Big, Small, 5) :- Big #< 5.
die_hard(empty_small, Small, Big, 0, Big) :- Small #> 0. die_hard(empty_small, Small, Big, 0, Big) :- Small #> 0.
@ -83,7 +81,6 @@ die_hard(big_to_small, Small, Big, S, B) :-
Small #< 3, Big #> 0, Small #< 3, Big #> 0,
big_to_small(Small, Big, S, B). big_to_small(Small, Big, S, B).
big_to_small(Small, Big, S, 0) :- big_to_small(Small, Big, S, 0) :-
Small + Big #=< 3, Small + Big #=< 3,
S #= Small + Big. S #= Small + Big.
@ -92,7 +89,6 @@ big_to_small(Small, Big, 3, B) :-
Small + Big #> 3, Small + Big #> 3,
B #= Big - (3 - Small). B #= Big - (3 - Small).
small_to_big(Small, Big, 0, B) :- small_to_big(Small, Big, 0, B) :-
Small + Big #=< 5, Small + Big #=< 5,
B #= Small + Big. B #= Small + Big.

View File

@ -1,6 +1,9 @@
:- use_module(library(clpfd)). :- use_module(library(clpfd)).
%-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=- %-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
%
% Program 18.3 from "Art of Prolog"
%
process(Program, ReducedProgram) :- process(Program, ReducedProgram) :-
findall(PC1, (member(C1, Program), preduce(C1, PC1), portray_clause(PC1)), ReducedProgram). findall(PC1, (member(C1, Program), preduce(C1, PC1), portray_clause(PC1)), ReducedProgram).
@ -23,13 +26,15 @@ test(Name, Program) :- program(Name, Clauses), process(Clauses, Program).
program(tundra, [ program(tundra, [
( thun([], S, S) ), ( thun([], S, S) ),
( thun( [Lit|E], Si, So) :- literal(Lit), thun(E, [Lit|Si], So) ), ( thun( [Lit|E], Si, So) :- literal(Lit), thun(E, [Lit|Si], So) ),
( thun( [Def|E], Si, So) :- def(Def, Body), append(Body, E, Eo), thun(Eo, Si, So) ),
( thun( [Func|E], Si, So) :- func(Func, Si, S), thun(E, S, So) ), ( thun( [Func|E], Si, So) :- func(Func, Si, S), thun(E, S, So) ),
( thun([Combo|E], Si, So) :- combo(Combo, Si, S, E, Eo), thun(Eo, S, So) ) ( thun([Combo|E], Si, So) :- combo(Combo, Si, S, E, Eo), thun(Eo, S, So) )
]). ]).
should_unfold(literal(Lit)).
should_unfold(def(Def, Body)).
should_unfold(func(Func, Si, So)). should_unfold(func(Func, Si, So)).
should_unfold(combo(A, B, C, D, E)). should_unfold(combo(A, B, C, D, E)).
should_unfold(literal(Lit)).
should_fold(sam, bill). should_fold(sam, bill).
%-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=- %-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
@ -66,6 +71,12 @@ combo(i, [P|S], S, Ei, Eo) :- append(P, Ei, Eo).
combo(dip, [P, X|S], S, Ei, Eo) :- append(P, [X|Ei], Eo). combo(dip, [P, X|S], S, Ei, Eo) :- append(P, [X|Ei], Eo).
combo(dipd, [P, X, Y|S], S, Ei, Eo) :- append(P, [Y, X|Ei], Eo). combo(dipd, [P, X, Y|S], S, Ei, Eo) :- append(P, [Y, X|Ei], Eo).
def(at,[drop,first]).
def(b,[[i],dip,i]).
def(binary,[unary,popd]).
% thun([binary|A], C, D) :- thun([unary, popd|A], C, D).
%-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=- %-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
% ?- test(tundra, _). % ?- test(tundra, _).