Game Description Language
A basic framework for representing games in Prolog has been provided by Stanford University’s General Game Playing course. The notes for the course written by Michael Genesereth include A Brief Introduction to Basic Logic Programming.
GDL
There are two dialects of Game Description Language, infix GDL which is nearly identical to Prolog, and a Lisp-like prefix GDL, called Knowledge Interchange Format, which is what the many examples provided at its public game repositories are written in.
I initially thought transliterating the game rules written in kif by the Stanford team to code runable by SWI-Prolog would be easy, but hit various idiosyncrasies of academic logic programing which seem awful from both human and computer readability to me.
Transliterating the following code in chess.kif to Prolog caused me hours of bug hunting which prompted me to start the thread The perils of unground variables in logic.
role(r)
means thatr
is a role in the game.base(p)
means thatp
is a base proposition in the game.input(r,a)
means thata
is a feasible action for roler
.init(p)
means that the propositionp
is true in the initial state.true(p)
means that the propositionp
is true in the current state.does(r,a)
means that roler
performs actiona
in the current state.next(p)
means that the propositionp
is true in the next state.legal(r,a)
means it is legal for roler
to play actiona
in the current state.goal(r,n)
means that player the current state has utilityn
for playerr
.terminal
means that the current state is a terminal state.
Alternating move games
legal(Player, noop):-
role(Player),
\+true(control(Player)).
Player moves from X1 (or Col1 or File1), Y1 (or Row1 or Rank1) to X2, Y2
Check if player has a piece in X1, Y1.
legal(Player,move(X1, Y1, X2, Y2)):-
role(Player),
true(control(Player)),
true(cell(X1, Y1, Player)).
Player can’t move onto own piece
Here’s a trap, because X2 and Y2 are not ground, so the following always fails due to Prolog’s negation as failure convention:
legal(Player, move(X1, Y1, X2, Y2)):-
role(Player),
true(control(Player)),
true(cell(X1, Y1, Player)),
\+true(cell(X2, Y2, Player))
To make this work, X2 and Y2 first need to be ground:
legal(Player, move(X1, Y1, X2, Y2)):-
role(Player),
true(control(Player)),
true(cell(X1, Y1, Player)),
true(cell(X2, Y2, CellContents)),
CellContents \= Player.
Cells
I wrote the following Prolog script to automate fetching games rules written in kif and translating them to prolog:
#!/usr/bin/env swipl
:- use_module(library(http/http_open)).
:- use_module(library(dcg/basics)).
:- initialization(main, main).
main(Argv) :-
last(Argv, Url),
setup_call_cleanup(
http_open(Url, Stream, []),
phrase_from_stream(lines(_Lines), Stream),
close(Stream)
).
lines([Line|Lines]) --> line(Line), !, lines(Lines).
lines([]) --> [].
line(Comment) --> comment(Cs), { string_codes(Comment, Cs), format('~w~n', [Comment]) }, !.
line(Whitespace) --> whitespace(Cs), { string_codes(Whitespace, Cs), format('~w', [Whitespace]) }, !.
line(Sexp) --> "(", s_expression(Sexp), ")", { format('~w.', [Sexp]) }.
s_expression(Sexp) --> blanks, term(Operator), blanks, terms(Args), { sexp(Operator, Args, Sexp) }.
sexp('<=', [Head|List], Sexp) :- !,
comma_list(Body,List),
Sexp =.. [':-',Head,Body].
sexp('not', Args, Sexp) :- !,
Sexp =.. ['\\+'|Args].
sexp('or', Args, SemicolonList) :- !,
semicolon_list(SemicolonList, Args).
sexp('distinct', Args, Sexp) :- !,
Sexp =.. ['\\='|Args].
sexp(Operator, Args, Sexp) :-
Sexp =.. [Operator|Args].
terms([Term|Terms]) --> blanks, term(Term), blanks, !, terms(Terms).
terms([]) --> [].
term(Sexp) --> "(", s_expression(Sexp), ")".
term(Variable) --> variable(Cs), { string_codes(Variable, Cs) }.
term(Symbol) --> symbol(Cs), { atom_codes(Symbol, Cs) }.
variable([U|Cs]) --> [63,L], { to_upper(L, U) }, symbol_rest(Cs).
symbol([C|Cs]) --> [C], { code_type(C, graph), string_codes("?();", Codes), \+ memberchk(C, Codes) }, symbol_rest(Cs).
symbol_rest([C|Cs]) --> [C], { code_type(C, graph), string_codes("();", Codes), \+ memberchk(C, Codes) }, symbol_rest(Cs).
symbol_rest([]) --> [].
comment([37|Cs]) --> ";", comment_rest(Cs).
comment_rest([37|Cs]) --> ";", comment_rest(Cs).
comment_rest([C|Cs]) --> [C], { \+ code_type(C, end_of_line) }, comment_rest(Cs).
comment_rest([]) --> [C], { code_type(C, end_of_line) }.
whitespace([C|Cs]) --> [C], { code_type(C, space) }, whitespace_rest(Cs).
whitespace_rest([]) --> [], !.
whitespace_rest([C|Cs]) --> [C], { code_type(C, space) }, whitespace_rest(Cs).
Then running say
./kif2prolog.pl http://games.ggp.org/base/games/buttons/buttons.kif > buttons.pl
would create a working Prolog file, though not pretty printed and also needing underscores for variables that aren’t used on the right-hand-side of rules.
I encountered a snag in my code with connectFourSimultaneous.kif which has a comment inside a statement. I found it easier to edit the kif file, but I should modify the above script to handle those cases sometime.
Rules for puzzles and games written in GDL need to define most of the above (base(p)
and input(r,a)
are mainly used for Propositional Nets which we won’t cover here). The above are easiest understood by looking at simple examples such as ButtonsAndLights and WolfGoatCabbage.
We’ll mimic sets using [[https://www.swi-prolog.org/pldoc/doc_for?object=sort/2|sort(+List, -Sorted)]] after gathering what’s currently true
using [[https://www.swi-prolog.org/pldoc/doc_for?object=findall/3|findall(+Template, :Goal, -Bag)]]. Sort ensures we don’t get duplicate bases and the order is consistent for state equality
(something that’s easy in Prolog, but a real pain in languages where lists are stored as pointers).
I’ve written findinits(Start)
like so, following a naming convention suggested by Genesereth in [[http://ggp.stanford.edu/notes/chapter_04.html|Chapter 4]] of his notes.
findinits(Start) :-
findall(Base, init(Base), Unsorted),
sort(Unsorted, Start).
In the case of ButtonsAndLights, that produces Start = [off(p), off(q), off(r), step(1)]
A convention followed by GDL is the base propositions in the current state are globally available to next(p)
, legal(r, a)
, goal(r, n)
, and terminal
as true(p)
. To make that work, we need to declare :- dynamic true/1, does/2.
at the top of our program.
To set the current state, we’ll use:
update_state(State) :-
retractall(true(_)),
forall(member(Base, State), assertz(true(Base))).
next(p)
rules typically expect the action the player selected to be globally available, so similarly we’ll do this:
update_does(Player, Action) :-
retractall(does(Player, _)),
assertz(does(Player, Action)).
Usually, legal(r,a)
rules would lookup true(p)
to get its results. ButtonsAndLights is an exception in that robot
can push buttons a, b, or c irrespective of what’s true in the current state.
To get a list of what the controlling player can do in the current state, we’ll use findlegals
, again using the naming convention from [[http://ggp.stanford.edu/notes/chapter_04.html|Chapter 4]]. Since this is going to be used as a helper for generatemoves(Parent, Moves)
, it’s assumed update_state(State)
has been called before this is used.
findlegals(Role, Legals) :-
findall(legal(Role, Action), legal(Role, Action), Unsorted),
sort(Unsorted, Legals).
In multiplayer games, Role would be obtained by a control(Player)
base proposition in the current state. For puzzles, we can look up the name of the sole player from role(robot)
in the case of ButtonsAndLights.
role(Player), findinits(Start), findlegals(Player, Start, Legals).
produces Legals = [legal(robot, a), legal(robot, b), legal(robot, c)]
ButtonsAndLights has very many next(p)
rules which illustrated the basics nicely. Looking at the first one:
next(on(p)) :-
does(robot, a),
true(off(p)).
Again following [[http://ggp.stanford.edu/notes/chapter_04.html|Chapter 4]] conventions, we’ll write a findnext(roles,move,state,game)
rule, but rearranged to work with maplist:
findnext(legal(Role, Action), Next) :-
update_does(Role, Action),
findall(Base, next(Base), Unsorted),
sort(Unsorted, Next).
The above assumes the state has already been set to true by findlegals
to be used with [[https://www.swi-prolog.org/pldoc/doc_for?object=maplist/3|maplist(:Goal, ?List1, ?List2)]] like so:
role(Player),
findinits(Start),
update_state(Start),
findlegals(Player, Legals),
maplist(findnext, Legals, Nexts)
This produces Nexts = [[off(q), off(r), on(p), step(2)], [off(p), off(q), off(r), step(2)], [off(p), off(q), off(r), step(2)]]
for Legals = [legal(robot, a), legal(robot, b), legal(robot, c)]
.
The final rule we need for generatemoves(Parent, Moves)
is to value each Next
(ie child) node, which I’ll call findreward
to follow Genesereth’s convention:
findreward(Role, State, goal(Role, Reward)) :-
update_state(State),
goal(Role, Reward).
Tying this all to together for generatemoves(Parent, Moves)
:
combinelists(_, [], [], [], []).
combinelists(State, [legal(Player, Action)|Legals], [Next|Nexts], [Goal|Goals],
[move(State, does(Player, Action), Next, Goal)|Moves]) :-
combinelists(State, Legals, Nexts, Goals, Moves).
generatemoves_(_, []) :-
terminal.
generatemoves_(Parent, Moves) :-
\+terminal,
role(Player),
findlegals(Player, Legals),
maplist(findnext, Legals, Nexts),
maplist(findreward(Player), Nexts, Rewards),
combinelists(Parent, Legals, Nexts, Rewards, Moves).
generatemoves(Parent, Moves) :-
update_state(Parent),
generatemoves_(Parent, Moves), !.
GDL uses semantics developed by Jacques Herbrand, explained by Genesereth in these notes which looks very much like Prolog. The alternative is Tarskian semantics which I can’t claim to have studied.
Every state in the game or puzzle is a set of true base propositions. The initial state for ButtonsAndLights looks like [off(p), off(q), off(r), step(1)]
, so we can find the depth from memberchk(step(Depth), Parent)
. We’ll use the same convention for WolfGoatCabbage, TowerOfHanoi etc.