Skip to content

Instantly share code, notes, and snippets.

@kamahen
Last active October 15, 2023 23:58
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save kamahen/a1448c4b1a0629dcf94a907e1b239a4e to your computer and use it in GitHub Desktop.
Save kamahen/a1448c4b1a0629dcf94a907e1b239a4e to your computer and use it in GitHub Desktop.
deadfish code improved
:- module(deadfish,
[deadfish/0,
deadfish/3, % for debugging
score_deadfish/1]).
% Deadfish is one of the best known non Turing-complete programming languages.
% It has only one accumulator (which starts at 0) to store data, and only four commands:
%
% i - Increment the accumulator
% s - Square the accumulator
% d - Decrement the accumulator
% o - Output the accumulator
%
% Create a program that will input a number and output Deadfish
% code to display the number. It must work for any integer from 0 to 255.
%
% https://codegolf.stackexchange.com/questions/40124/short-deadfish-numbers/
% https://swi-prolog.discourse.group/t/autum-challenge-short-deadfish-numbers/6869
% Using:
% https://swi-prolog.discourse.group/t/dealing-with-state/6866/10
% Op<StateName to operate on the various state variables. Op is one of
%
% List<StateName for a normal DCG terminal
% String<StateName for a SWI-Prolog string acting as a terminal
% Callable<StateName. When found, we call call(Callable, V0, V) to
% update the state for StateName
% :- set_prolog_flag(optimise, true). % For the arithmetic statements
% The various predicates used by deadfish_eval//0
% (but these are compiled out by goal expansion):
% value(V, V, V).
% set_value(V, _, V).
% not_value(X, V, V) :- X \= V.
% incr(X0, X) :- X is X0 + 1 .
% decr(X0, X) :- X0 > 0, X is X0 - 1 .
% TODO: not_value(X)<prv is used instead of
% [V]<prv, { V \= X }
% because the DCG expansion adds a V0=V1
% which looks like '#'(A,B,C,D)='#'(F,G,H,I)
% and isn't necessary.
% square(X0, X) :- X0 > 1, X is X0*X0 .
square(NumSqLimit, X0, X) :- X0 > 1, X0 =< NumSqLimit, X is X0*X0.
% TODO: this goal doesn't get executed because the situation it tries
% to deal with happens in the compiler, after all term and goal
% expansion:
'expand_#_equals'('#'(Acc1,Ops1,Prv1,Out1,Num1,Nsq1),
'#'(Acc2,Ops2,Prv2,Out2,Num2,Nsq2),
Goals) =>
Goals =
( Acc1=Acc2,
Ops1=Ops2,
Prv1=Prv2,
Out1=Out2,
Num1=Num2,
Nsq1=Nsq2
).
'expand_#_equals'(_, _, _) => fail.
% 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 using the same name.
expand_record(Literal,Name,State0,State, Goal), is_list(Literal) =>
get_set_record(Name, State0, List, State, Tail),
append(Literal, Tail, List),
Goal = true.
expand_record(String,Name,State0,State, Goal), string(String) =>
get_set_record(Name, State0, List, State, Tail),
string_codes(String, Literal),
append(Literal, Tail, List),
Goal = true.
expand_record(value(Value),Name,State0,State, Goal) =>
get_set_record(Name, State0, V0, State, V),
Goal = (Value=V0, V0=V).
expand_record(set_value(Value),Name,State0,State, Goal) =>
get_set_record(Name, State0, _V0, State, V),
Goal = (V = Value).
expand_record(not_value(NotValue),Name,State0,State, Goal) =>
get_set_record(Name, State0, V0, State, V),
V0 = V,
Goal = (NotValue \= V0).
expand_record(incr,Name,State0,State, Goal) =>
get_set_record(Name, State0, V0, State, V),
Goal = (V is V0 + 1).
expand_record(decr,Name,State0,State, Goal) =>
get_set_record(Name, State0, V0, State, V),
Goal = (V0 > 0, V is V0 - 1).
expand_record(Step,Name,State0,State, Goal), callable(Step) =>
extend_goal(Step, [V0,V], StepEx),
get_set_record(Name, State0, V0, State, V),
Goal = StepEx.
goal_expansion(<(On, Name,State0,State), Goal) :-
expand_record(On, Name, State0, State, Goal).
goal_expansion(A=B, Goals) :-
'expand_#_equals'(A, B, Goals).
% 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).
:- det(get_set_record/5).
% args same as get_dict/5
% get_set_record(Name, Rec, V0, NewRec, V) :-
% RecName_Name(Rec, V0),
% set_Name_of_RecName(V, 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).
:- use_module(library(record)).
dcg_record_name('#').
:- record '#'( % must match dcg_record_name/1
acc, % accumulator
ops, % list of opcodes
prv, % previous opcode
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 :-
forall(between(1,255,N),
( min_deadfish(N, Ops),
string_chars(OpsStr, Ops),
writeln(N:OpsStr)
)).
score_deadfish(Score) :-
findall(X, (between(1,255,N),
deadfish_time(N, X)), Xs),
maplist(deadfish_length, Xs, Lens),
sum_list(Lens, Score).
deadfish_length(_Inferences:_N:_Ops:Len:_Cpu, Len).
deadfish_time(N, X) :-
call_time(min_deadfish(N, Ops),T),
length(Ops, Len),
X=T.inferences:N:Ops:Len:T.cpu.
min_deadfish(Num, Ops) :-
between(1, 100000000, OpsLen),
deadfish(Num, OpsLen, Ops),
!.
deadfish(Num, OpsLen, Ops) :-
number_digits(Num, Ds),
NumSqLimit is floor(sqrt(Num + 1)) + 1, % probably can be less
'make_#'([acc(0), ops(Ops), out(Ds), prv(-), num(Num), nsq(NumSqLimit)], State0),
'make_#'([acc(_), ops([]), out([]), prv(_), 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//0 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 -->
[o]<ops,
set_value(o)<prv,
value(Acc)<acc,
number_digits(Acc).
deadfish_eval -->
[s]<ops,
set_value(s)<prv,
value(NumSqLimit)<nsq,
square(NumSqLimit)<acc.
deadfish_eval -->
not_value(d)<prv, % value(Prev)<prv, { Prev \= d },
[i]<ops,
set_value(i)<prv,
incr<acc.
deadfish_eval -->
not_value(i)<prv, % value(Prev)<prv, { Prev \= i},
[d]<ops,
set_value(d)<prv,
decr<acc.
% number_digits//1 outputs the digits in Number to accumulator `out`
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(123, [1,2,3]).
number_digits(Number, Digits) :-
'make_#'([out(Digits)], S0),
'make_#'([out([])], S),
call_dcg(number_digits(Number), S0, S).
end_of_file.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment