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).