Frontier Software

Buttons and Lights

This is a simple example puzzle translated from a kif file into SWI Prolog. The full code is on Swish where the query route(Actions) gives two answers

The puzzle consists of three lights labeled p, q, and r, each of which can be on or off, giving us 8 possible states (provided we ignore the state’s step counter). The player moves from state to state by pressing one of three buttons, labelled a, b, or c and the object is to get to the final state with 6 button presses.

Since the puzzle has to be solved in 7 moves (a common trick to prune game trees from growing too large) and there are the same 3 possible actions per move, the graph consists of 21 move(State0, Action, State1, Goal) records if step(N) bases are excluded. The reason there aren’t 3 * 8 arcs is the final state is game over.

Below is the state machine the puzzle represents I drew using Hugo’s Go ASCII Tool after Graphviz’s dot refused to allign the step 4 choices for some reason.

b o n ( p ) , o n ( o o o q o o o f n f ) n f f f ( f , ( f f ( p ( c p ( ( p ) p o ) p p ) , ) a f , ) ) , , f , , o ( o o a f b o r f b o o f f n a ) c f n a f f ( ( ( ( f ( q q q q ( q ) ) ) ) q ) a , b , , b , ) , , o o c o a o o o f f f n n o f f f f ( ( f f ( ( ( r r f ( r r p a ) ) ( r ) ) ) r ) c , ) o b c f c , f c ( q ) , o n ( r ) b

init(Base)

The starting state is all three lights off, which the rules represent with init(Base) rules.

init(off(p)).
init(off(q)).
init(off(r)).
init(step(1)).

findinits(Start) explained in Puzzle Solving produces

Start = [off(p), off(q), off(r), step(1)]

The object of the game is to get all three lights on, represented in the rules like so:

goal(robot, 100) :- 
    true(on(p)), 
    true(on(q)), 
    true(on(r)).

legal(Role, Action)

The player robot has the option of pressing one of three buttons a, b, or c each turn, represented in code like so:

legal(robot, a).
legal(robot, b).
legal(robot, c).

In Buttons and Lights, findlegals(Role, Legals) produces Legals = [legal(robot, a), legal(robot, b), legal(robot, c)]. Note, however, that for most GDL games or puzzles, legal(R, A) are rules which assume the current state has been set with update_state(State) before legals are queried.

next(Base)

The next(Base) predicates expect the current state to be available for global lookup as true(Base) and the player’s selected move as does(Player, Action). Buttons and Lights has 18 next(P) clauses plus one to advance step(N) each turn to codify the above state machine.

next(on(p)) :- 
    does(robot, a), 
    true(off(p)).

next(on(q)) :- 
    does(robot, a), 
    true(on(q)).

next(on(r)) :- 
    does(robot, a), 
    true(on(r)).

next(off(p)) :- 
    does(robot, a), 
    true(on(p)).

next(off(q)) :- 
    does(robot, a), 
    true(off(q)).

next(off(r)) :- 
    does(robot, a), 
    true(off(r)).

next(on(p)) :- 
    does(robot, b), 
    true(on(q)).

next(on(q)) :- 
    does(robot, b), 
    true(on(p)).

next(on(r)) :- 
    does(robot, b), 
    true(on(r)).

next(off(p)) :- 
    does(robot, b), 
    true(off(q)).

next(off(q)) :- 
    does(robot, b), 
    true(off(p)).

next(off(r)) :- 
    does(robot, b), 
    true(off(r)).

next(on(p)) :- 
    does(robot, c), 
    true(on(p)).

next(on(q)) :- 
    does(robot, c), 
    true(on(r)).

next(on(r)) :- 
    does(robot, c), 
    true(on(q)).

next(off(p)) :- 
    does(robot, c), 
    true(off(p)).

next(off(q)) :- 
    does(robot, c), 
    true(off(r)).

next(off(r)) :- 
    does(robot, c), 
    true(off(q)).

next(step(Y)) :- 
    true(step(X)), 
    succ(X, Y).

findnext(legal(Role, Action), Next) assumes the current state is globally available. findinits(Start), update_state(Start), findnext(legal(robot, a), Next). produces Next = [off(q), off(r), on(p), step(2)].

Without drawing out the state diagram, there are no clues other than trial and error to figure out the correct sequence. The rules limit the player to 6 actions.

terminal :- 
    true(step(7)).

From the above diagram we can see two possible strings will get us from start to goal:

  1. abacba
  2. abcaba

The search space we want iterative_deepening to produce looks like this:

buttons1.svg

Lets get to the above step-by-step. The start looks like this:

findinits(Start), 
getchildren(Start, Graph1).

Without cycle removal, the opening moves look like this:

buttons2.svg

Now lets expand to move 2:

findinits(Start), 
getchildren(Start, _Graph1),
depthfirst(2, _Graph1, [], Graph2).

buttons3.svg

Including step(N) is a common way to remove cycles, but has the drawback of possibly turning an 8 node graph into a pyramid of doom with in this example possibly 3^7 = 2187 nodes.

To remove cycles, we need to remove the step(N) base from each state, which is easily done using [[https://www.swi-prolog.org/pldoc/doc_for?object=select/3|select(?Elem, ?List1, ?List2)]].

removestep(move(Parent, _, _, _), NoStep) :-
    select(step(_), Parent, NoStep).

cycle(Limit, NoSteps, move(Parent, _, Child, _)) :-
    member(step(Limit), Parent),
    select(step(_), Child, NoStep),
    memberchk(NoStep, NoSteps).

prune(Limit, Unpruned, Pruned) :-
    maplist(removestep, Unpruned, NoSteps),
    exclude(cycle(Limit, NoSteps), Unpruned, Pruned).

Using it in the above as so

findinits(_Start), 
getchildren(_Start, _Graph1),
prune(1, _Graph1, _NoCycles1),
depthfirst(2, _NoCycles1, [], _Graph2),
prune(2, _Graph2, NoCycles2).

To strip the graph down to:

buttons4.svg

We can repeat the above recursively until we get to solution like so:

iterative_deepening(_, Graph, Graph) :-
    memberchk(move(_, _, _, goal(_, 100)), Graph).

iterative_deepening(Depth, GraphIn, Acc) :-
    \+memberchk(move(_, _, _, goal(_, 100)), GraphIn),
    depthfirst(Depth, GraphIn, [], Unpruned),
    Unpruned \== GraphIn,
    prune(Depth, Unpruned, GraphOut),
    succ(Depth, Limit),
    iterative_deepening(Limit, GraphOut, Acc).

By stripping out cycles, the only terminal we reach in this puzzle is the solution. In WolfGoatCabbage, we get a problem space that’s not only full of cycles, but also “dead leaf” nodes which can be pruned out to keep the search space skinny.