Last night I realised that my bottom-up parser generator was broken. I fixed it quite quickly this morning --- a name was misspelled --- and wrote a little compiler to test it. I'll show it here as an example of the absolute bare minimum compiler written in a very high level language.
So, here is the prolog source code for a lambda calculus reducer and compiler.
The input language is the basic lambda calculus described here in a grammar that is used to generate a bottom-up parser. This grammar is left-recursive so top down parsers would have trouble with it.
Code: Select all
%%% slask/parser.bup
parse(E) ::= exp(E), ['.'].
exp(variable(V)) ::= variable(V).
exp(abstraction(V, E)) ::= [lambda], variable(V), exp(E).
exp(application(E1, E2)) ::= exp(E1), exp(E2).
exp(E) ::= ['('], exp(E), [')'].
variable(V) ::= [V], {atom(V), V \== '(', V \== ')', V \== lambda}.
The compiler takes the output from the parser and generates terms for a reduction machine. In this case Krivine's machine.
Code: Select all
%%% slask/compiler.pl
:- ensure_loaded('slask/parser').
rho_lookup(VariableName, Rho, Result) :-
rho_lookup(VariableName, Rho, 0, Result).
rho_lookup(VariableName, [], _, _) :- throw(semantic_error(undefined_variable(VariableName))).
rho_lookup(VariableName, [VariableName|_], Result, Result) :- !.
rho_lookup(VariableName, [_|Rest], Counter, Result) :-
NewCounter is Counter + 1,
rho_lookup(VariableName, Rest, NewCounter, Result).
extend_rho(Var, Rho, [Var|Rho]).
compile_lambda_exp(variable(Var), Rho, #Dbn) :-
rho_lookup(Var, Rho, Dbn).
compile_lambda_exp(abstraction(Var, Body), Rho, abstraction(BodyCode)) :-
extend_rho(Var, Rho, ExtendedRho),
compile_lambda_exp(Body, ExtendedRho, BodyCode).
compile_lambda_exp(application(Operator, Operand), Rho, application(OperatorCode, OperandCode)) :-
compile_lambda_exp(Operator, Rho, OperatorCode),
compile_lambda_exp(Operand, Rho, OperandCode).
compile_lambda(Input, Output) :-
goal(parse, [Expression], Input, []),
compile_lambda_exp(Expression, [], Output).
This is Krivine's reduction machine. It is probably the simplest abstract machine you could get for this purpose.
Code: Select all
%%% slask/krivine.pl
krivine([suspension(Env, Exp)|_], #0, Stack, Result) :-
!,
krivine(Env, Exp, Stack, Result).
krivine([_|Rest], #N, Stack, Result) :-
!,
M is N-1,
krivine(Rest, #M, Stack, Result).
krivine(Env, application(Operator, Operand), Stack, Result) :-
krivine(Env, Operator, [suspension(Env, Operand)|Stack], Result).
krivine(Env, abstraction(Exp), [Top|Tail], Result) :-
!,
krivine([Top|Env], Exp, Tail, Result).
krivine([], T, [], T).
Here is the code that ties it all together. Note the use of read_in/1 to tokenise input. No need for a tokeniser here!
Code: Select all
:- op(200, fx, #).
:- ensure_loaded('slask/compiler').
:- ensure_loaded('slask/krivine').
:- ensure_loaded(runtime(readin)).
main_loop :-
read_in(Input),
compile_lambda(Input, Code),
krivine([], Code, [], Result),
format('~p~n', [Result]),
main_loop.
Just to show that it works, we see that when we apply the identity function to an argument, we get the argument back. The output
abstraction(abstraction(#1)) is equivalent to
(lambda y (lambda z y)), basically a function which takes an argument then returns a function which takes a second argument then discards it and returns the first argument. The
#1 says go up the call stack by one argument and return that value.
Code: Select all
| ?- ['slask/main'].
% yes
| ?- main_loop.
|: (lambda x x) (lambda y (lambda z y)).
abstraction(abstraction(#1))
|:
Doesn't look like much and it is very inefficient, but it is an implementation of a simple lazy functional language which has covered argument passing and functions as first-class values. All that is needed now is typed data (integers, chars, lists), delta reductions (primitive functions, e.g., +, *, /, print, read). It would also be pretty easy to introduce syntactic sugar, e.g., "let V=N in E" translated into "(lambda V E) N". Once it was working they way you wanted it to, you could start thinking about changing the abstract machine into something that would give you much better performance. Then, finally, bootstrap the compiler and runtime system into the language defined.
For more info, see
Abstract Machines, A Lambda Calculus Perspective, Werner Kluge.