Dealing with state

I believe this is Mercury solution to this problem.
Has anyone ever implemented this in pure prolog ?
Won’t this need a custom neck with term_expansion in order to implement ?

Thanks for the Mercury pointer. I know some people did something similar for their own use. And no, you do not need a custom neck if you reserve the special term. Now if I recall correctly, defining ! as a prefix operator is somewhat dubious in pure Prolog. Not sure how serious that is.

Having a reserved term is somewhat problematic if you happen to need that term. The way around is typically to use e.g., =../2, so code that requires a match against !(X) has to do Term =.. [!,X]. That currently also holds for SWI-Prolog’s ‘.’ for functional notation. In practice, this seems manageable as long as you use a term that is rarely seen in normal Prolog source code.

edit for reference: The Mercury Language Reference Manual: State variables

Did a little experiment. See attached file below. With this, we can write the code below to end up with the code you would write by hand as well. Now, this is also not a good example.

sv_sumlist(List, Sum) :-
    sv_sumlist(List, 0, Sum).

sv_sumlist([], !_).
sv_sumlist([H|T], !Sum) :-
    !:Sum is H+!.Sum,
    sv_sumlist(T, !Sum).

There surely are good examples as threading state variables in the body is a very common thing to do. Below is an example reading terms from a file and performing some selection and transformation on them. Note that we introduce the state variable in the head using !:S to get access to the final state. Next we we use !:S again to introduce a fresh variable (a successor without a current). From there we do the state transitions.

tf(File, !:S) :-
    read_file_to_terms(File, !:S, []),
    exclude(junk, !S),
    maplist(transform, !S).

Again, the question is how much sense does this make? The fact that Mercury went for it is an encouragement. To complete it we must notably add IDE support as the highlighting and GUI tracer get pretty confused. Program analysis runs on the transformed code, so that keeps working fine.

Not well tested …

state_vars.pl (8.2 KB)

Long time friends, I guess… :joy: but I mean: everyone in here expects Jan to be the master, SWI-Prolog is in large part his creature (a little bit like Frankenstein’s), so I think it would be difficult to imagine a different outcome

It is hard to find people < 30 years old who have > 30 years of programming experience.

3 Likes

Indeed looks wrong. It isn’t well tested. I only looked at disjunctions operating on the same state variable. Disjunctions is probably the hardest part of the code. Well, I haven’t looked into interaction with meta_predicate/1 declarations either.

The question is first of all whether it makes sense to support this part of Mercury? Maybe it is better to improve edcgs (e.g., module awareness and maybe some more to reduce the need for declarations)?

Interesting (note that the link is wrong). I guess it mostly works well for Python that, if I recall correctly, by default using functional notation, so

X := foo(1, X)

Translates to Mercury-style

foo(1, !.X, !:X) 

or simply

foo(1, !X).

Without using functional notation it gets less nice as we would get

foo(1, X, Y),
X := Y

right? Well, of course we could translate X := foo(1,X) into call(foo(1,!.X), !:X) and do something special for arithmetic? That leads to some ambiguity as e.g. the function sin(X) has in SWI-Prolog no relation to a possible predicate sin/2, so what would X := sin(X) do?

I’m not sure that a logo like this might appeal to the mathematician or to the logician or to the academic. You should choose something that looks more intimidating and reserved exclusively to the very smart

You’re right. A mascot is not what I had in mind. I was thinking of logos more in general. And in that case I had in mind a thing (not a mascot) like a lambda symbol that you can find in many logos of Lisp-related languages for example

Here is my attempt at implementing the syntax I proposed above using the goal_expansion technique from Jan.
So, from this dcg predicate:

q -->
   state(o(key, value)).

this will expand to:

?- set_setting(backend, rbtrees).
true.

?- listing(q).
q(A, A) :-
    (   rb_lookup(key, value, A)
    ->  true
    ;   existence_error(key, key, A)
    ).

?- set_setting(backend, dict).

?- make.

?- listing(q).
q(A, A) :-
    (   get_dict(key, A, value)
    ->  true
    ;   existence_error(key, value, A)
    ).

?- set_setting(backend, record).

?- make.

?- listing(q).
q(A, A) :-
    state_data(key, A, value).

setting/updating one or multiple states and calling non-dcg predicates with appended states also works.

Also not very well tested :slight_smile:

state.pl (4.0 KB)

You can use the set or update syntax since when dealing with states instead of lists, push-back is just a way of stepping the state:

state(+(key, NewValue)).  % set syntax
state(-(key, OldValue, NewValue)).  % update syntax

You just need to make sure that the update is the last update in your predicate.

An alternative is to modify @jan’s goal expansion as follows – this gave me ~40% performance improvement for my “deadfish” code (see Autum Challenge: Short Deadfish Numbers). Possibly this wouldn’t be needed if get_dict/5 can be compiled to inline code (the overhead seems to be mainly in the call to the predicate; the code below gains most of its performance improvement by doing the “record” expansion inline, as if library(record) generated macros for expanding its predicates when used as goals).

Modified goal expansion
goal_expansion(<(On, Name,State0,State), Clause) :-
    expand_record(On, Name, State0, State, Clause).

% expand_record/2 uses record expansion instead of a dict, for faster
% performance. There must be a dcg_record_name/1 fact and an
% appropriate `:- record` directive.
expand_record(Literal,Name,State0,State, Clause), is_list(Literal) =>
    get_set_record(Name, State0, List, State, Tail),
    Clause = true,
    append(Literal, Tail, List).
expand_record(String,Name,State0,State, Clause), string(String) =>
    get_set_record(Name, State0, List, State, Tail),
    Clause = true,
    string_codes(String, Literal),
    append(Literal, Tail, List).
expand_record(Step,Name,State0,State, Clause), callable(Step) =>
    extend_goal(Step, [V0,V], StepEx),
    get_set_record(Name, State0, V0, State, V),
    Clause = ( % Clause0,
               StepEx
             ).

% get_set_record/5 is a bit more complicated because
% library(record) doesn't generate the equivalent of:
%   get_set_<name>_of_<constructor>(Rec, V, NewRec, NewV) :-
%       <constructor>_<name>(Rec, V),
%       set_<name>_of_<constructor>(NewV, Rec, NewRec).

get_set_record(Name, Rec, V0, NewRec, V) :-
    dcg_record_name(RecName),
    call_univ([RecName, '_', Name], [Rec, V0]),
    call_univ([set_, Name, '_of_', RecName], [V, Rec, NewRec]).

call_univ(PredParts, Univ) :-
    concat_atom(PredParts, Pred),
    Call =.. [Pred|Univ],
    call(Call).
Example of using record-expansion DCG
:- use_module(library(record)).

dcg_record_name(df).

:- record df( % must match dcg_record_name/1
              acc,              % accumulator
              ops,              % list of opcodes
              out,              % result of running the opcodes,
              num, % the number to be output (for limiting search space)
              nsq  % see deadfish/3 (for limiting search space)
            ).

deadfish(Num, OpsLen, Ops) :-
    number_digits(Num, Ds),
    NumSqLimit is floor(sqrt(Num + 1)) + 1, % probably can be less
    % State0 = #{acc:0, ops:Ops, out:Ds, num:Num, nsq:NumSqLimit},
    % State  = #{acc:_, ops:[],  out:[], num:Num, nsq:NumSqLimit},
    make_df([acc(0), ops(Ops), out(Ds), num(Num), nsq(NumSqLimit)], State0),
    make_df([acc(_), ops([]),  out([]), num(Num), nsq(NumSqLimit)], State),
    call_dcg(seq_of_len(OpsLen, deadfish_eval), State0, State).

seq_of_len(0, _) --> [].
seq_of_len(Len, P) -->
    { Len > 0 },
    call(P),
    { Len2 is Len - 1 },
    seq_of_len(Len2, P).

% deadfish_eval//2 computes a sequence of opcodes (in `ops`), the
% accumulator (in `apps`), and the resulting output (in `out`).
% For pruning the searchspace, there are `num` and `nsq`.

deadfish_eval -->
    [s]<ops,
    value(NumSqLimit)<nsq,
    square(NumSqLimit)<acc.
deadfish_eval -->
    [i]<ops,
    incr<acc.
deadfish_eval -->
    [d]<ops,
    decr<acc.
deadfish_eval -->
    [o]<ops,
    value(Acc)<acc,
    number_digits(Acc).

% The various predicates used by deadfish_eval//0:

value(V, V, V).

incr(X0, X) :- X is X0 + 1 .

decr(X0, X) :- X0 > 0, X is X0 - 1 .

square(X0, X) :- X0 > 1, X is X0*X0 .
square(NumSqLimit, X0, X) :- X0 > 1, X0 =< NumSqLimit, X is X0*X0.

number_digits(Number) -->
    { Number =< 9 }, !,
    [Number]<out.
number_digits(Number) -->
    { divmod(Number, 10, Number2, D) },
    number_digits(Number2),
    [D]<out.

output_digits([]) --> [].
output_digits([D|Ds]) -->
    [D]<out,
    output_digits(Ds).

% number_digits/2 is a convenience wrapper for number_digits//1.

number_digits(Number, Digits) :-
    make_df([out(Digits)], S0),
    make_df([out([])], S),
    % S0 = #{out:Digits},
    % S  = #{out:[]},
    call_dcg(number_digits(Number), S0, S).
1 Like

This is magic!

Never managed to understand EDSG – can’t get my head around the declarations …

And, this simply simply works …