Is there a way to serialize continuation or program execution state?

I’m thinking about how to save/load game state in SWI-Prolog.

Here is the code skeleton of my game:

main.pl

:- dynamic script_iterator/2.

init_iterator(Goal, Iterator) :-
  reset(Goal,YE,Cont),
  (   Cont == 0
  ->  Iterator = done
  ;   YE = yield(Element)
  ->  Iterator = next(Element, Cont)
  ).

next(next(Element,Cont), Element, Iterator) :-
  init_iterator(Cont, Iterator).

yield(Term) :-
  shift(yield(Term)).
  
wait_frames(0) :- !.
wait_frames(N) :-
  yield(_),
  N1 is N - 1,  
  wait_frames(N1).

%% -- game loop --

game_update(FrameID) :-
  format("game_update FrameID=~w~n", [FrameID]),
  forall(script_iterator(Goal, Iterator),
         (   Iterator \= done
         ->  next(Iterator, _, NewIterator),
             retract(script_iterator(Goal, Iterator)),
             assertz(script_iterator(Goal, NewIterator))
         ;   true         
         )         
        ).

game_init :-
  load_files('script.pl'),
  init_iterator(on_game_init, Iterator),
  assertz(script_iterator(on_game_init, Iterator)).
  
game_fini :-
  retractall(script_iterator(_,_)),  
  unload_file('script.pl').

main :-
  game_init,
  game_update(1),
  game_update(2),
  game_update(3),
  game_update(4),
  game_update(5),
  game_update(6),  
  game_update(7),
  game_update(8),
  game_fini.

Note that this game is very flexible, it loads another Prolog file script.pl. Game designers or players can write their own script.pl to extend game logic.

script.pl

on_game_init :-
  writeln("Hello, this game will start in 5 frames"),
  wait_frames(5),
  writeln("Game start!")
  %% ... other logic ...
  .

Notice that the script supports the “wait N seconds” feature. Here I use frames instead of seconds for simplicity.

A query for first 8 frames:

?- main.
Hello, this game will start in 5 frames
game_update FrameID=1
game_update FrameID=2
game_update FrameID=3
game_update FrameID=4
game_update FrameID=5
Game start!
game_update FrameID=6
game_update FrameID=7
game_update FrameID=8

It works well.

My question is that if the game needs to support SAVE/LOAD, what should I do? For example, at the 3rd frame, the player might click the SAVE button in the menu and exit the game. How do I serialize the continuation state for script_iterator/2?

I have tried the library(persistency), but it doesn’t work for continuations.

A feasible workaround is to write a Meta-Interpreter, which seems not difficult in Prolog, but what’s the drawbacks of using Meta-Interpreter. Does Meta-Interpreter scale well to other SWI-Prolog features?

Besides Meta-Interpreter, is there any other way to solve this problem? For example, is it possible to run a Prolog program inside a sandbox and the sandbox supports serializing/deserializing?.

Thanks in advance for any advice.

As is, there is no way to serialize the full execution state of SWI-Prolog. In the old days several Prolog systems had save_program(File), which would create a File that was executable and when executed would simply continue at the end of the save_program/1. That was based on an old Unix utility called undump, which took a core dump as input and created a new executable from it. Undump still seems to exist. I gave up on it at some point because there were too many limitations and portability is too hard.

These days you can do such things using virtual machines. Sounds a bit like an overkill.

A continuation may be enough, but note that it doesn’t capture the entire state. Notably choice points are not part of it. The continuation cannot be saved and restored because it contains clause references. You could work around that by rewriting the continuation and replace the source reference with other information to identify the clause (such as being the Nth clause of a specific predicate using nth_clause/3). Then the restore needs to find the corresponding clauses, after which you can call the continuation :slight_smile: Make sure the program does not change as the continuation also holds offset pointers into the executable code of the clause, so resuming a modified clause will pretty surely crash.

You can get that done completely in Prolog. Note there is no need for library(persistency) as that is intended to deal with a gradually changing set of clauses, not with a one-time dump and restore.

A more fundamental approach would be to serialize the entire Prolog execution state (i.e., the stacks and VM registers) in such a form that we can restore it (again, mostly replacing pointers with descriptions of what it is pointing at such that we can restore the data). The critical part is again the clauses. We could save these as above or save them along with the state (which would require some work to merge them with the state of the program in the context it is reloaded. There are options though :slight_smile: ).

This touches a bit on an older idea to introduce a thread_fork/1 predicate that would create a new thread with semantics close to the POSIX fork() system call, i.e., the new thread is a clone of the old one except for the “return” of the thread_fork/1 call which tells the old one the identifier of the clone and the clone that it is a clone (possibly also providing the thread it is cloned from). This is relatively simple as the execution context (atoms, clauses, etc) is the shared.

In both scenarios, it is still hard/impossible to grab the C stack state, so it only works if the calling thread does not have interleaved Prolog → C → Prolog calls.

2 Likes

As much as it is overkill it is practical, works and often used as a starting or stop gap measure but once in place and working tends to be left as is.

I asked a related question concerning theorem provers here and noted two possible work arounds.

  1. Docker Checkpoint & Restore - Requires running in a Docker container.
  2. VMWare Suspend and Resume - Requires running in VMWare virtual machine.

I think so too. Other game data are all first-order (no closures, low-level pointers, etc), they can be serialized easily.

Do you mean to modify the delimited continuations’ source code? This is a bit of a challenge for me :smiling_face: (this may require more WAM knowledge?).


You didn’t mentioned Meta-Interpreter. How about this approach?

From my personal view,

Prolog’s Meta-Interpreter seems more powerful than other languages (e.g. Lisp).

For example, in Lisp, pattern-matching is a macro, if you write a naive Meta-Interpreter in Lisp, you cannot get the ability automatically, whereas, in Prolog, unification is built-in, you essentially obtain pattern-matching for free.

Also, in Prolog, since everything is a term, Meta-Interpreter can call any goals directly.

For examples:

If the game scripts want built-in predicates, just write:

eval(Goal,Signal) :-
  predicate_property(Goal, built-in), !,
  call(Goal),
  Signal = ok.

then we can use = in the game scripts.

If the game script want the predicates from module apply, just write:

eval(Goal,Signal) :-
  predicate_property(Goal, imported_from(apply)), !,
  call(Goal),
  Signal = ok.

then we can use somthing like maplist([X] >> format("~w~n", [X]), [1,2,3]) in the game scripts.

In other words, as long as we don’t use term expansion features (e.g. DCG or CHR), there is nothing else has to be done, is that right? Of course, the Meta-Interpreter must deal with the interaction between cut and delimited continuations.

Could you give some comments on the pros and cons of Meta-Interpreter in Prolog? Does it work in practice? AFAIK, no one uses Lisp Meta-Interpreter in practice, but Prolog seems to be a bit different.

Thanks!

No. The continuation is just a Prolog term. The only problem is that it contains references to clauses that are in the end simply pointers. E.g.

t(Cont) :-
    reset(t2, _Ball, Cont).

t2 :-
    write(a),
    shift(done),
    write(b).
?- t(X).
a
X = call_continuation(['$cont$'([], <clause>(0x55e67cad9680), 9)]).

Now <clause>(0x55e67cad9680), is a reference to the t2/0 clause. You can figure that out using nth_clause/3 or clause_property/2. So, you turn that into e.g. '$CLAUSE'(t20, 1) to indicate the clause. Then you have a term you can save. Now at restore you find the clause reference and replace your placeholder with it. Next you can call the continuation.

I don’t really see how it helps. Does it avoid the need for continuations? Or are you also going to implement the whole continuation stuff in the meta interpreter? In any case, you typically loose a factor 10 in performance.

2 Likes

Yes, that is what I mean. Just give the meta interpreter an additional argument for continuations (a stack of goals), see Schrijvers et al., 2013 (preprint PDF) section 3 for details.

1 Like

I think I understand what you mean. I am trying to manually construct a continuation term.

For example,

t(Cont) :-
    reset(t2, _Ball, Cont).

t2 :-
    writeln(a),
    shift(done),
    writeln(b).

?- t(Cont).
a
Cont = call_continuation([$cont$([],<clause>(0000000000364B60),9)]).

?- nth_clause(t2, 1, Reference),
    Cont = call_continuation(['$cont$'([],Reference,9)]).
Reference = <clause>(0000000000324290),
Cont = call_continuation([$cont$([],<clause>(0000000000364B60),9)]).

However, when calling the Cont, an ERROR occurred:

?- nth_clause(t2, 1, Reference),
   Cont = call_continuation([$cont$([],Reference,9)]), call(Cont).
ERROR: Type error: `continuation' expected, found `'$cont$'([],<clause>(0000000000364B60),9)' (a compound)
ERROR: In:
ERROR:   [11] call_continuation(['$cont$'([],<clause>(0000000000364B60),9)])
ERROR:   [10] '<meta-call>'(user:user: ...) <foreign>
ERROR:    [9] toplevel_call(user:user: ...) at c:/program files/swipl/boot/toplevel.pl:1117

I just used compound_name_arguments/3 to compose/decompose continuations:

?- nth_clause(t2, 1, Reference), compound_name_arguments(ContInternal, '$cont$', [[], Reference, 9 | []]),
   Cont = call_continuation([ContInternal]), call(Cont).
b
Reference = <clause>(0000000000354290),
ContInternal = $cont$([],<clause>(0000000000354290),9),
Cont = call_continuation([$cont$([],<clause>(0000000000354290),9)]).

It works :slightly_smiling_face:, I don’t know why though.

You’d have to try, but I fear it is way too slow. I don’t recall all the details, but most likely this didn’t deal with cuts. Dealing with cuts is surely possible, especially for systems that have prolog_cut_to/1 to implement cuts with a larger scope.

:slight_smile: This goes rather deep. The implementation of call_continuation/1 makes life a little harder: It knows the term created by shift/1 has no internal references, while the one you have does. You can hack around that using duplicate_term/2 which creates a duplicate of the term with no unnecessary references.

r :-
    nth_clause(t2, 1, Reference),
    Cont = call_continuation(['$cont$'([],Reference,9)]),
    duplicate_term(Cont, Cont2),
    call(Cont2).

Now:

?- r.
b.

Make sure to fasten seat belts before using :slight_smile:

2 Likes

Thanks.

Disturb you again, could you explain a little further (it is not related to the topic though):

It knows the term created by shift/1 has no internal references, while the one you have does.

What do you mean by “the term created by shift/1 has no internal references” ? P.s. I also successfully created the continuation term by compound_name_arguments/3, which is also OK, but I don’t know why.

Thanks again!

A Prolog term is one of the usual things (atom, int, …, compound, var). Internally, there is one more thing: references. You can see the need for this best after running A = B. Now A and B become the same variable. This is done by making A a reference to B. Binding the combined variable will follow the reference chain and fill the value at the end. Using the variable also follows the reference chain to find the actual value. There are some more reasons why the system creates references while creating terms. shift/1 however doesn’t use this, so the continuation term is free of these and call_continuation/1 simply makes this assumption rather than checking all parts of the continuation term to be a reference and following it. One may call it unsafe. That is not really the case as it is easy enough to create continuation terms that will crash the system and if we would need to validate the continuation for safety before calling it it will be a lot of code and slow. So, the only thing you can safely use is the result of shift/1. If you want to escape from this you need to know what you are doing :slight_smile:

Thanks.

Is the reference you mentioned related to e.g. <clause>(0000000000354290)?

My understanding is that the term created by shift/1 includes an actual reference, i.e. <clause>(0000000000354290), instead of a logic variable Reference, but what I create manually includes a logic variable Reference (we must replace it with actual value <clause>(0000000000354290) ), is that right?

Is a reference really a blob? e.g. Blob types

No. These things are blobs, which is a super type of atom that is often used as a safe reference to gobal data such as the clause. This allows for safe garbage collection of such objects and guarantees that the handle can always be used safely.

A reference in the sense we are talking about is an internal thing that is never visible from the Prolog user world. If you want to understand these, check the literature on the WAM Prolog VM (not used by SWI-Prolog, but in this respect they are the same).

2 Likes

The book Warren’s Abstract Machine A Tutorial Reconstruction is always in my reading-list. I will read it eventually, thanks!

Hi @jan, do you know the whole schema of the $cont$ term? I found some partial information in tabling.pl

user:portray(Cont) :-
    ...
    compound_name_arguments(Cont, '$cont$', [_Context, Clause, PC | Args]),

The problem is the Args, which means $cont$ has different variants. For example,

call_continuation([$cont$([],<clause>(0000000002B461C0),4,2,<inactive>),
                   $cont$([],<clause>(0000000002948AD0),18,<inactive>,<inactive>,
                          [$cont$([],<clause>(0000000002948AD0),18,<inactive>,<inactive>,
                                  [$cont$([],<clause>(0000000002948AD0),18,<inactive>,<inactive>,
                                          [$cont$([],<clause>(0000000002AC43D0),15)],_16700)],_16678)],
                          _16656)])

As you see, $cont$ can have 3, 5, or 7 arguments (maybe more) and some arguments can be a List which nests $cont$, but I don’t know the whole schema of the data type. For example, can the 4th argument of $cont$ contain nested $cont$?


Nevertheless, I also wrote a more general version:

:- module(serialization, [serialize/2, deserialize/2]).

serialize(Term, STerm), blob(Term, clause) =>
  nth_clause(Pred, Index, Term),  
  STerm = '$CLAUSE'(Pred, Index).
serialize(Term, STerm), \+ compound(Term) =>
  STerm = Term.
serialize(Term, STerm), is_list(Term) =>
  maplist([In, Out]>>serialize(In, Out), Term, STerm).
serialize(Term, STerm), Term =.. [Name | Args] =>
  maplist([In, Out]>>serialize(In, Out), Args, SArgs),
  STerm =.. [Name | SArgs].

deserialize('$CLAUSE'(Pred, Index), Term) =>
  nth_clause(Pred, Index, Term).
deserialize(STerm, Term), \+ compound(STerm) =>  
  Term = STerm.
deserialize(STerm, Term), is_list(STerm) =>
  maplist([In, Out]>>deserialize(In, Out), STerm, Term).
deserialize(STerm, Term), STerm =.. [Name | SArgs] =>
  maplist([In, Out]>>deserialize(In, Out), SArgs, Args),
  Term =.. [Name | Args].

This version works well (even in complex scenarios, e.g. my game). It just replaces all occurrences of $cont$ with $CLAUSE and vice versa. The drawback is the (1) potential name collision (e.g. an accidental use of $CLAUSE, the probability is low though) (2) there may be some compound terms (other than List and functor) that I haven’t take into account. Also, this version has to be written in two predicates. I found it difficult to write a bidirectional conversion. I would appreciate if anyone could write a bidirectional version. That would be more relational flavor.


Could you provide more hints about how to serialize stacks and VM registers (e.g. which Prolog interfaces have to be used)? I will explore further. It seems that the above two predicates (i.e. serialize/2 and deserialize/2) can be reused. P.s. not an urgent task.

Thanks.

There is no full spec, only a rough description in src/pl-cont.c:

'$cont$'(Module, Clause, PC, EnvArg1, ...)

Here, Module is the context module for transparent predicates or [] for normal predicates. Clause is the clause, PC is the program counter inside the clause, EnvArg1 is an array holding the frame arguments in the same order as the frame layout. The atom ‘’ is used for frame slots that are not accessed by the remainder of the continuation.

So, the clause only appears as 2nd argument of the ‘cont’ terms. Of course, if the Prolog code processes blobs you have a problem (for example, (…) refers to some I/O stream). The 4th and later arguments are Prolog data structures (the number depends on the variables in the clause). It is quicker and safer to leave them alone. Note that you can use fast_write/1 (and friends) for read/write of the continuation. This binary read/write can handle attributes, cyclic terms, etc. The downside is that the compatibility is not guaranteed (except between minor versions of the stable releases). For continuations that is not much of a problem as there are no promises besides they work in the currently running Prolog instance.

1 Like

I don’t quite understand the statement… :sweat_smile:

Could you explain further? Thanks.

I desire the spec because the Args in $cont$ may contain nested $cont$s or List of $cont$s (or other structures I don’t know?). It would be nice if we could focus on those places that only contains $cont (It is not a big problem though :wink:).

Nevertheless, I have written a new version, which is more general than the old one. Now it only focus on $cont$ functors instead of blob clauses.

serialize(Term, STerm), \+ compound(Term) =>
  STerm = Term.
serialize(Term, STerm), is_list(Term) =>
  maplist([In, Out] >> serialize(In, Out), Term, STerm).
serialize(Term, STerm), Term =.. ['$cont$', Module, Clause, PC | Args] =>
  maplist([In, Out] >> serialize(In, Out), Args, SArgs),
  nth_clause(Pred, Index, Clause),  
  STerm =.. ['$cont$', Module, '$CLAUSE'(Pred, Index), PC | SArgs].
serialize(Term, STerm), Term =.. [Name | Args] =>
  maplist([In, Out] >> serialize(In, Out), Args, SArgs),
  STerm =.. [Name | SArgs].

deserialize(STerm, Term), \+ compound(STerm) =>  
  Term = STerm.
deserialize(STerm, Term), is_list(STerm) =>
  maplist([In, Out] >> deserialize(In, Out), STerm, Term).
deserialize(STerm, Term), STerm =.. ['$cont$', Module, '$CLAUSE'(Pred, Index), PC | SArgs] =>
  maplist([In, Out] >> deserialize(In, Out), SArgs, Args),
  nth_clause(Pred, Index, Clause),
  Term =.. ['$cont$', Module, Clause, PC | Args].
deserialize(STerm, Term), STerm =.. [Name | SArgs] =>
  maplist([In, Out] >> deserialize(In, Out), SArgs, Args),
  Term =.. [Name | Args].

It works well currently (haven’t considered Module yet).


I cannot use fast_write/1 in my computer.

Welcome to SWI-Prolog (threaded, 64 bits, version 8.4.1)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.

For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).

?- use_module(library(fastrw)), fast_write(foo(123)).
ERROR: No permission to fast_write stream `current_output'
ERROR: In:
ERROR:   [12] fast_write(current_output,foo(123))
ERROR:    [9] toplevel_call(user:user: ...) at c:/program files/swipl/boot/toplevel.pl:1117
ERROR: 
ERROR: Note: some frames are missing due to last-call optimization.
ERROR: Re-run your program in debug mode (:- debug.) to get more detail.

Also I didn’t find any interface that has a +Stream argument in library(fastrw).

It might actually be a false claim. shift/1 produces a list of '$cont$'() terms, so it would be enough to simply replace each 2nd arguments of the ‘cont’ term in the list. That is safer because the application Prolog data at the end of the ‘cont’ term may contain stuff that is relatively hard to deal with in Prolog such as attributed variables, cyclic terms, shared subterms, etc. The fast_write/1 predicate family can deal with these.

However, if a continuation is called and something in this continuation again calls shift/1 you will end up with continuation data structures somewhere in what is in the above description the application Prolog data. So, you have to go through the whole data structure :frowning:

You can deal with cycles and sharing using term_factorized/3 and with constraints using copy_term/3.

You cannot write that to the swipl-win console. Works fine with a binary file. fast_write/2 and fast_read/2 do exist, but I see they are documented elsewhere because they are built-in. The library only provides additional predicates for compatibility with some other Prolog systems.

1 Like

Yes. That’s exactly what I’m worried about.

A possible workaround is to limit the some usages of game scripts (I admit that it is appealing to allow game designers / players to use attribute variables in the scripts though, e.g. CLP, CHR, etc).

I have not met attributed variables, cyclic terms, shared subterms, but I will remember your advice.

Thanks.