implement a simple C like language in Prolog?
Asked Answered
D

2

6

I'm new to prolog, so this's quite a challenge to me. I'm supposed to implement a simple C like language in Prolog.

the ultimate goal is to be able to execute something like this:
?- run([begin,a,:=,10,while,a,>,5,begin,write,a,a,:=,a,-,1,end,end]).

and get: 
10 
9
8
7
6 
yes

However, I'm stuck at the first step. This is what I have achieved so far. out of local stack!

statement(Vars,_Vars) --> assign(Vars,_Vars).
statement(Vars,Vars2) --> statement(Vars,Vars1), statement(Vars1,Vars2). 

assign(Vars,_Vars) --> default_assign(Vars,_Vars).
assign(Vars,_Vars) --> simple_assign(Vars,_Vars).

% a //default value 0
default_assign(Vars,_Vars) --> 
    var_name(Var_Name),
    {update_vars([Var_Name,0],Vars,_Vars)}.

% a = 0
simple_assign(Vars,_Vars) --> 
    var_name(Var_Name),[=],var_value(Var_Value),
    {update_vars([Var_Name,Var_Value],Vars,_Vars)}.

% a = b
simple_assign(Vars,_Vars) --> 
    var_name(Var_Name1),[=],var_name(Var_Name2),
    {
    update_vars([Var_Name1,Var_Value],Vars,_Vars)
    }.

var_name(Var_Name) --> [Var_Name],{\+number(Var_Name2)}.    
var_value(Var_Value) -->[Var_Value],{number(Var_Value)}.

% found match, update
update_vars(Var,Vars,_Vars):-
    member(Var,Vars),
    update(Var,Vars,_Vars),
    _Vars\==[].
% no match, append
update_vars(Var,Vars,_Vars):-
    \+member(Var,Vars),
    append(Var,Vars,_Vars).

update([Name,Value],[],[]).
update([Name,Value],[[Name,Old_Value]|T1],[[Name,Value]|T2]):-
    update([Name,Value],T1,T2).
update([Name,Value],[[Name1,Value1]|T1],[[Name1,Value1]|T2]):-
    [Name,Value]\=[Name1,Value1],
    update([Name,Value],T1,T2).

append([Name,Value],[],[[Name,Value]]).
append([Name,Value],[H|T1],[H|T2]):-
    append([Name,Value],T1,T2).

Here's my logic. First I want to be able to consume the list(that's how I interpret it - -!), so the grammar structure is really really important. And I'm also thinking about using a variable list 'Vars' in forms of [[Name,Value],[a,1],[b,2]...], and an updated version - '_Vars'. So I can pass it to other statements like while loop and write.

statement(Vars,Vars2) --> statement(Vars,Vars1), statement(Vars1,Vars2).
% this seems wrong...

But... It looks like the logic is wrong from the beginning. :\ below is the simplified version. I would really appreciate it if you can help me out here. And I really hope I won't take this with me in Christmas. T.T

statement --> assign.
statement --> statement, statement.

assign --> simple_assign.
assign --> default_assign.

default_assign --> 
    var_name(Var_Name).
simple_assign --> 
    var_name,[=],var_value.

var_name --> 
    [Var_Name],{\+number(Var_Name)}.    
var_value -->
    [Var_Value],{number(Var_Value)}.
Deane answered 17/12, 2013 at 10:28 Comment(4)
C-like, are you sure? This looks terribly like Pascal :)Goles
This is an interesting exercise, unlike anything I've seen.Manchu
Haha. I'll keep this post updated.Deane
my final solution here: github.com/iqhash/interpreter/tree/master/c-in-prologDeane
P
2

This is how I would go about it:

  1. transform the source code into a abstract syntax tree

    begin 
      a := 1
      while a < 5
      begin
        a := a + 1;
      end
    end
    

    becomes

    statements([
        assign(a, number(1)),
        while(greater(variable(a), number(5))), 
              statements([
                  assign(a, plus(variable(a), number(1)))
                         ])
             )
               ])
    
  2. build an interpreter for it.

    There are various interpreters. The easiest one is the vanilla interpreter. Here is one I would begin with:

    interpret(number(N), State, N, State).
    interpret(assign(Variable, Statement), State, Value, NewState) :- 
        interpret(Statement, State, Value, NewState1), 
        assignVariable(Variable, Value, NewState1, NewState).
    
Peart answered 17/12, 2013 at 11:10 Comment(3)
this structure it's already implicitly handled by DCG, as used in OP's question.Fitts
The problem I'm facing right now is recursion pattern, and updating and passing variables list. But thanks anyway. abstract syntax tree kind of rings a bell.Deane
I think you may be able to circumvent recursion by using repeat and bind and unbind variables OR using a list of all states with an unbound variable in the end that is specialized for every repeat OR using assert and retract.Peart
F
2

Your code seems appropriate, just some typo around, resulting in singletons, that probably harm the soundness of your attempt.

There are + 2 singletons in simple_assign (Var_Name2 and Var_Value), and + Var_Name2 is singleton in var_name

I guess you're not using and IDE with proper syntax highlighting...

edit singletons apart, I must say that User' answer is more useful than mine (+1). Attempting to provide a modifiable environment while parsing doesn't work. Here is how I tested, with a somewhat different version of your grammar:

test :-
    phrase(statement(S), [begin,a,:=,10,while,a,>,5,begin,write,a,a,:=,a,-,1,end,end]),
    eval(S, [], _).

% grammar

statement(Var := Expr) --> var(Var), [:=], expr(Expr).
statement(write(E)) --> [write], expr(E).
statement(while(C, S)) --> [while], condition(C), statement(S).
statement(S) --> [begin], statements(S), [end].

statements([S|R]) --> statement(S), statements(R).
statements([]) --> [].

condition(L > R) --> expr(L), [>], expr(R).

expr(L - R) --> (var(L) ; num(L)), [-], expr(R).
expr(E) --> (var(E) ; num(E)).

var(var(V)) --> [V], {atom(V)}.
num(num(N)) --> [N], {number(N)}.

% evaluation

eval([S|R], Vs, Us) :- eval(S, Vs, V1), eval(R, V1, Us).
eval([], Vs, Vs).

eval(V := E, Vs, Us) :-
    exprv(E, Vs, Ve),
    ( select(V := _, Vs, R) -> Us = [V := Ve | R] ; Us = [V := Ve | Vs] ).
eval(write(E), Vs, Vs) :- exprv(E, Vs, Ve), writeln(Ve).
eval(while(C, S), Vs, Ts) :-
    satisfied(C, Vs) -> eval(S, Vs, Us), eval(while(C, S), Us, Ts) ; Vs = Ts.

% no side effect here

exprv(L-E, Vs, Ve) :- exprv(L, Vs, Vl), exprv(E, Vs, R), Ve is Vl - R.
exprv(num(N), _, N).
exprv(var(V), Vs, Vv) :- memberchk(var(V) := Vv, Vs).

satisfied(L > R, Vs) :- exprv(L, Vs, Vl), exprv(R, Vs, Vr), Vl > Vr.
Fitts answered 17/12, 2013 at 11:56 Comment(2)
thanks guys. I'm using text mate with a prolog syntax highlight plug in. and I tend to ignore singletons..Deane
@Deane You shouldn't ignore singletons since they may point to a bug.Idiot

© 2022 - 2024 — McMap. All rights reserved.