Skip to content

Instantly share code, notes, and snippets.

@K9-guardian
Last active December 5, 2022 20:27
Show Gist options
  • Save K9-guardian/f1f1527f6b8144770a2ca23a282a3517 to your computer and use it in GitHub Desktop.
Save K9-guardian/f1f1527f6b8144770a2ca23a282a3517 to your computer and use it in GitHub Desktop.
Brainfuck interpreter in SWI-Prolog.
:- use_module(library(apply)).
:- use_module(library(assoc)).
:- use_module(library(clpfd)).
:- use_module(library(dcg/basics)).
:- use_module(library(dcg/high_order)).
:- use_module(library(edcg)).
:- use_module(library(pio)).
:- use_module(library(portray_text)).
% I'd prefer to use characters but this is a compromise to make the code simpler.
:- set_prolog_flag(back_quotes, codes).
:- portray_text(true).
:- set_portray_text(min_length, 0).
:- set_portray_text(ellipsis, 1_000). % Make this as long as you need.
% AST is a list of terms. For paired brackets, wrap the list in a loop functor.
cmd('>') --> `>`.
cmd('<') --> `<`.
cmd('+') --> `+`.
cmd('-') --> `-`.
cmd('.') --> `.`.
cmd(',') --> `,`.
% expr ::= "" | cmd expr | [ expr ] expr.
expr([]) --> [].
expr([V|Vs]) --> cmd(V), expr(Vs).
expr([loop(Ls)|Vs]) --> `[`, expr(Ls), `]`, expr(Vs).
edcg:acc_info(bytes, K-(V0-V), Bs0, Bs, get_assoc(K, Bs0, V0, Bs, V)).
edcg:acc_info(pointer, X, Ptr0, Ptr, Ptr #= Ptr0 + X).
edcg:acc_info(input, C, [C|In], In, true).
edcg:acc_info(output, C, [C|Out], Out, true).
edcg:pred_info(get_bytes_pos, 1, [bytes, pointer]).
edcg:pred_info(cmds_state_, 1, [bytes, pointer, input, output]).
get_bytes_pos(V) -->> Ptr/pointer, Bs/bytes, { get_assoc(Ptr, Bs, V) }.
cmds_state_([]) -->> [].
cmds_state_(['>'|Cmds]) -->> [1]:pointer, cmds_state_(Cmds).
cmds_state_(['<'|Cmds]) -->> [-1]:pointer, cmds_state_(Cmds).
cmds_state_(['+'|Cmds]) -->>
Ptr/pointer,
{ V #= (V0 + 1) mod 256 },
[Ptr-(V0-V)]:bytes,
cmds_state_(Cmds).
cmds_state_(['-'|Cmds]) -->>
Ptr/pointer,
{ V #= (V0 - 1) mod 256 },
[Ptr-(V0-V)]:bytes,
cmds_state_(Cmds).
cmds_state_(['.'|Cmds]) -->> get_bytes_pos(V), [V]:output, cmds_state_(Cmds).
cmds_state_([','|Cmds]) -->>
Ptr/pointer,
[V]:input,
[Ptr-(_-V)]:bytes,
cmds_state_(Cmds).
cmds_state_([loop(Cmds0)|Cmds]) -->>
get_bytes_pos(V),
( V == 0
-> cmds_state_(Cmds)
; cmds_state_(Cmds0),
cmds_state_([loop(Cmds0)|Cmds])
).
% Runs a brainfuck program from a list of codes.
prog_in_out(Program, Input, Output) :-
numlist(1, 30000, Ks), maplist([K, K-0]>>true, Ks, Ps), list_to_assoc(Ps, Bs),
tfilter([V, T]>>memberd_t(V, `><+-.,[]`, T), Program, Stripped),
phrase(expr(Cmds), Stripped),
cmds_state_(Cmds, Bs, _, 1, _, Input, _, Output, []).
% Same as above predicate but with a file input for the program.
file_in_out(File, Input, Output) :-
numlist(1, 30000, Ks), maplist([K, K-0]>>true, Ks, Ps), list_to_assoc(Ps, Bs),
phrase_from_file(string(Program), File),
tfilter([V, T]>>memberd_t(V, `><+-.,[]`, T), Program, Stripped),
phrase(expr(Cmds), Stripped),
cmds_state_(Cmds, Bs, _, 1, _, Input, _, Output, []).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment