Introduction
Dogelog Player is a Prolog system mostly written in Prolog itself. It is available for the JavaScript, Python and Java platform. It offers a minimalistic subset of the ISO core standard for Prolog, dubbed by the name Novacore.
Picture generated with xAI Grok
It further features a minimalistic library to access the Browser environment. The content of the library is developed with hindsight of its usage in Dogelog Notebooks. Here we give a glimps of its usage for Game Sprites.
Markup Library
When it comes to the Browser environment, unlike other Prolog systems such as Tau-Prolog or SWI-Prolog WASM, we do not only embrace HTML, but also SVG, MathML, etc.. anything that has a XML serialization.
The library for generating output is library(markup), it features only two predicates tag/1
and tag_format/2
. It works via side effects, similar like the predicates write/1
, nl/0
, etc.. already do in the ISO core standard.
-
tag(A):
The predicate succeeds. As a side effect it emits the tagA
-
tag_format(T, L):
The predicate succeeds. It first formats the templateT
with the
with the argument listL
into an atomA
and the callstag(A)
The predicates are agnostic whether the output is HTML, SVG, MathML, etc.. The below shows an example output that can be placed inside a SVG element and that will define a fill pattern with a given ID:
back(ID) :-
tag('<defs>'),
tag_format('<pattern id="~a" width="50" height="40" patternUnits="userSpaceOnUse">', [ID]),
tag('<image href="tile.jpg" width="50" height="40"/>'),
tag('</pattern>'),
tag('</defs>'),
tag_format('<rect width="500" height="400" fill="url(#~a)"/>', [ID]).
Under the hood we use an enhanced format/2
routine that also understands the ~a
place holder and does XML escaping. There is also a predicate format_atom/3
exposed, that returns an atom instead of formatting into the current output.
Scalable Games
Somehow most Prolog systems neglect SVG, scalable vector graphis. The Tau-Prolog little dog example works with HTML elements and not with SVG elements. The little dog is now a show case of SWI-Prolog WASM, but still using only HTML elements.
We believe SVG has some potential for game design since it offers flexible coordinate systems. With a little programming discipline this makes it possibly to design games for different screen resolutions. To ease the production of SVG we introduced the library(vector):
draw(X, Y, A, ID) :-
format_atom('translate(~e,~e) rotate(~e)', [X,Y,A], T),
svg_text(0, 0, '🪰', [id(ID),transform(T),
style('font-size: 24px; text-anchor: middle; dominant-baseline: middle')]),
flush_output.
The above draws a game sprite derived from the unicode character 0x1FAB0
. Like an emoji it is multicolored and can have quite some detail when scaled. We use 24px
, a font size relative to the viewport, so that the game sprites scale with the viewport.
Further tricks here are text anchor middle and dominant baseline middle which determines the reference point of the game sprite in the center of the unicode character. Further tricks are then a transformation which allows us to rotate the unicode character:
:- svg_begin([id(kitchen)]), back(wall),
draw(250, 150, 0, fly),
draw(200, 200, -90, fly1),
draw(300, 200, 90, fly2),
draw(250, 250, 180, fly3),
svg_end, nl.
The result inside a Dogelog Notebook is then:
React Library
The react library provides among other things event handling as already pioneered by Tau-Prolog. It differs in that we don't deliver any browser environment getter or setters. Instead the idea is that library(react) complements the library(markup), in that it allows diverting from the linear output:
-
tag_goto(I):
The predicate succeeds. As a side effect the cursor
is set to the element with idI
-
tag_remove:
The predicate succeeds. As a side effect the cursor
is removed and set to its parent
It is obvious that while tag/1
and tag_format/2
do create DOM elements, that we can remove DOM elements with tag_goto/1
and tag_remove/0
. Less obvious and maybe debatable, we can also update DOM elements by simply recreating them. Here is an example of making a fly buzz around:
buzz(0, _, _, _, _) :- !.
buzz(I, X, Y, A, ID) :-
R is A*pi/180,
random(V), W is V*10,
X2 is X+W*sin(R),
Y2 is Y-W*cos(R),
random(U), A2 is A+U*30-15,
shield((tag_goto(ID),
tag_remove,
draw(X2, Y2, A2, ID))),
I2 is I-1,
sleep(200), % measured in milliseconds
buzz(I2, X2, Y2, A2, ID).
The result inside a Dogelog Notebook is then:
Task Groups
The shield/1 meta predicate has the effect that auto-yielding is switched off temporarily. It can be used for a critical region. In the implementation of the buzz/5 predicate it is used to make the browser DOM update atomic. We can now run multiple flies via create_task/1:
flies(0, _) :- !.
flies(I, ID) :-
format_atom('flies~w', [I], ID2),
create_task(fly(ID, ID2)),
I2 is I-1,
sleep(1000), % measured in milliseconds
flies(I2, ID).
This is gives an interesting problem for Dogelog Notebook orchestration. The first challenge is that flies/2
can terminate before all fly/2
tasks have terminated. We therefore introduced a new JavaScript async function group_gather_async()
that waits for all tasks to terminate:
try {
await perform_async(new Compound("ensure_loaded", ["user"]));
await group_gather_async();
perform("flush_output");
} catch (err) {
group_teardown();
perform(new Compound("sys_print_error", [err]));
}
Both the Dogelog Notebook main task execution via ensure_loaded/1
and the completion wait of the non-main tasks are interruptible. If the current cell is aborted in either case an exception results and the remaining non-main tasks are signalled via group_teardown()
.
The result inside a Dogelog Notebook is then:
Conclusions
With a little programming discipline the library(vector) makes it possibly to design games for different screen resolutions. To ease the Dogelog Notebook orchestration of the animation of multiple game sprites via cooperative multitasking from create_task/1
, we introduced group_gather_async()
and group_teardown()
.
Example 12: Fly Swatter
https://www.xlog.ch/runtab/doclet/docs/11_advanced/example12/package.html