Skip to content

Instantly share code, notes, and snippets.

@Joelbyte
Last active January 16, 2021 12:34
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save Joelbyte/a62ad46e2941dc1006cc153b2b63c1ec to your computer and use it in GitHub Desktop.
Save Joelbyte/a62ad46e2941dc1006cc153b2b63c1ec to your computer and use it in GitHub Desktop.
BASIC in Prolog
:- use_module(library(assoc)).
%Version 0.1 of PROLOG BASIC.
%Author: Victor Lagerkvist.
%License: not sure, as long as I'm not responsible for anything.
%TODO: comment everything. :(
%Run the program corresponding to StatementList (see the end of this
%file for a concrete example). Try the query: example_program(P),
%run(P, Comp).
run(StatementList, Comp) :-
statement_list_to_program(StatementList, Program),
init_comp(Program, Comp0),
interpret_line(Comp0, ok, Comp).
%Parse a list of statements to the internal tree format.
statement_list_to_program([N:S], Tree) :-
empty_assoc(Tree0),
set(Tree0, N, S:int(void), Tree1),
set(Tree1, int(void), end:int(void), Tree).
statement_list_to_program([N1:S1, N2:S2|Rest], Tree) :-
statement_list_to_program([N2:S2|Rest], Tree0),
set(Tree0, N1, S1:N2, Tree).
%Initialize the comp object with the given program.
init_comp(Program, comp{mem:M, stack:[], program:Program, line:Start, status:ok}) :-
empty_mem(M),
%Find the starting line (the node in the tree with the lowest key).
min_assoc(Program, Start, _).
%Fundamental operations of the comp object.
empty_mem(S) :- empty_assoc(S).
get(S, Var, Val) :- get_assoc(Var, S, Val).
get_mem(Comp, Var, Val) :- get(Comp.mem, Var, Val).
get_line(Comp0, Comp0.line).
get_status(Comp0, Comp0.status).
get_statement_and_increment_line(Comp0, Command, Comp0.put([line:NewLine])) :-
get(Comp0.program, Comp0.line, Command:NewLine).
push(Comp0, E, Comp0.put([stack:[E|Comp0.stack]])).
pop(Comp0, E, Comp0.put([stack:Stack])) :-
[E|Stack] = Comp0.stack.
set(S0, Var, Val, S) :- put_assoc(Var, S0, Val, S).
set_end_state(Comp, Comp.put([status:end])).
set_line(Comp0, Line, Comp0.put([line:Line])).
set_mem(Comp0, Var, Val, Comp0.put([mem:NewMemory])) :-
set(Comp0.mem, Var, Val, NewMemory).
%%Predicates relating to the interpreter.
%Interpret a single line as long as the status is 'ok'.
interpret_line(Comp0, ok, Comp) :-
get_statement_and_increment_line(Comp0, S, Comp1),
interpret_statement(Comp1, S, Comp2),
get_status(Comp2, Status),
interpret_line(Comp2, Status, Comp).
interpret_line(Comp, end, Comp).
%Interpret a single statement.
interpret_statement(Comp0, goto(Label), Comp) :-
set_line(Comp0, Label, Comp).
interpret_statement(Comp0, end, Comp) :- set_end_state(Comp0, Comp).
interpret_statement(Comp, skip, Comp).
interpret_statement(Comp, print(Id), Comp) :-
get_mem(Comp, Id, V),
write(V),
nl.
interpret_statement(Comp0, gosub(Label), Comp) :-
get_line(Comp0, Line),
push(Comp0, Line, Comp1),
interpret_statement(Comp1, goto(Label), Comp).
interpret_statement(Comp0, return, Comp) :-
pop(Comp0, Line, Comp1),
set_line(Comp1, Line, Comp).
interpret_statement(Comp0, let(id(I), E), Comp) :-
eval_exp(Comp0, E, V),
set_mem(Comp0, id(I), V, Comp).
interpret_statement(Comp0, if(B, GotoLine), Comp) :-
eval_bool(Comp0, B, Res),
interpret_if(Res, Comp0, GotoLine, Comp).
%Pop a for-statement from the stack, increase the for variable,
%evaluate the Boolean expression, set the current line to the line of
%the for statement, and interpret the for statement (while informing the
%for statement that the line of the next statement is CurrentLine).
interpret_statement(Comp0, next(Id), Comp) :-
pop(Comp0, ForLine:for(Id, Start, End, Step), Comp1),
eval_exp(Comp1, Id + Step, NewVal),
set_mem(Comp1, Id, NewVal, Comp2),
eval_bool(Comp2, Id < End, Res),
get_line(Comp2, LineAfterNext),
set_line(Comp2, ForLine, Comp3),
interpret_for(Res, Comp3, for(Id, Start, End, Step), LineAfterNext, Comp).
interpret_statement(Comp0, for(Id, Start, End, Step), Comp) :-
eval_exp(Comp0, Start, StartVal),
set_mem(Comp0, Id, StartVal, Comp1),
interpret_for(1, Comp1, for(Id, Start, End, Step), void, Comp).
interpret_for(0, Comp0, for(_,_,_,_), LineAfterNext, Comp) :-
interpret_statement(Comp0, goto(LineAfterNext), Comp).
interpret_for(1, Comp0, for(Id, Start, End, Step), _LineAfterNext, Comp) :-
get_line(Comp0, ForLine),
push(Comp0, ForLine:for(Id, Start, End, Step), Comp).
interpret_if(0, Comp, _, Comp).
interpret_if(1, Comp0, GotoLine, Comp) :-
interpret_statement(Comp0, goto(GotoLine), Comp).
%%Predicates evaluating arithmetic and Boolean expressions.
%We currently only support integers. :(
eval_exp(_, int(Exp), Exp).
eval_exp(Comp, id(Exp), V) :-
get_mem(Comp, id(Exp), V).
eval_exp(Comp, E1 + E2, V) :-
eval_exp(Comp, E1, V1),
eval_exp(Comp, E2, V2),
eval_plus(V1, V2, V).
eval_exp(Comp, E1 - E2, V) :-
eval_exp(Comp, E1, V1),
eval_exp(Comp, E2, V2),
eval_sub(V1, V2, V).
eval_exp(Comp, E1 * E2, V) :-
eval_exp(Comp, E1, V1),
eval_exp(Comp, E2, V2),
eval_mult(V1, V2, V).
%We use these auxillary predicates rather than using is/2 directly
%since we might want to change the implementation of numbers
eval_plus(V1, V2, V) :- V is V1 + V2.
eval_sub(V1, V2, V) :- V is V1 - V2.
eval_mult(V1, V2, V) :- V is V1 * V2.
eval_bool(Comp, E1 < E2, Result) :-
eval_exp(Comp, E1, V1),
eval_exp(Comp, E2, V2),
compare(Order, V1, V2),
eval_le(Order, Result).
eval_bool(Comp, E1 =< E2, Result) :-
eval_exp(Comp, E1, V1),
eval_exp(Comp, E2, V2),
compare(Order, V1, V2),
eval_leq(Order, Result).
eval_bool(Comp, E1 > E2, Result) :-
eval_exp(Comp, E1, V1),
eval_exp(Comp, E2, V2),
compare(Order, V1, V2),
eval_ge(Order, Result).
eval_bool(Comp, E1 = E2, Result) :-
eval_exp(Comp, E1, V1),
eval_exp(Comp, E2, V2),
compare(Order, V1, V2),
eval_eq(Order, Result).
eval_le(<, 1).
eval_le(=, 0).
eval_le(>, 0).
eval_leq(<, 1).
eval_leq(=, 1).
eval_leq(>, 0).
eval_eq(<, 0).
eval_eq(=, 1).
eval_eq(>, 0).
eval_ge(<, 0).
eval_ge(=, 0).
eval_ge(>, 1).
eval_geq(<, 0).
eval_geq(=, 1).
eval_geq(>, 1).
%A small example program computing 10!.
example_program(
[
int(10):let(id(x),int(1)),
int(20):for(id(i),int(1),int(10),int(1)),
int(30):let(id(x),id(x)*id(i)),
int(40):next(id(i))
]).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment