1:- module(rolog, 2 [ 3 r_init/0, 4 r_init/1, 5 r_call/1, 6 r_eval/2, 7 op(600, xfy, ::), 8 op(800, xfx, <-), 9 op(800, fx, <-), 10 op(100, yf, []), 11 '<-'/2, 12 '<-'/1 13 ]). 14 15:- use_foreign_library(foreign(rolog)). 16:- use_module(library(terms)). 17 18r_init :- 19 current_prolog_flag(os_argv, [Argv0 | _]), 20 r_init(Argv0). 21 22:- op(800, xfx, <-). 23:- op(800, fx, <-). 24 25r_call(Expr) :- 26 pl2r_(Expr, R), 27 r_eval_(R). 28 29r_eval(X, Y) :- 30 pl2r_(X, R), 31 r_eval_(R, Y). 32 33pl2r_('::'(Namespace, Compound), X) 34 => term_string(Namespace, Ns), 35 compound_name_arguments(Compound, Name, Arguments), 36 pl2r_('do.call'($(getNamespace(Ns), Name), Arguments), X). 37 38pl2r_(A =< B, X) 39 => pl2r_('<='(A, B), X). 40 41pl2r_(A[B], X) 42 => pl2r_('['(A, B), X). 43 44pl2r_({}, X) 45 => X = 'NULL'. 46 47pl2r_({A; B}, X) 48 => pl2r_curly({A; B}, C), 49 S =.. [';' | C], 50 X = '{'(S). 51 52pl2r_({A}, X) 53 => pl2r_(A, C), 54 X = '{'(C). 55 56pl2r_(Hash, X), 57 compound(Hash), 58 compound_name_arguments(Hash, #, Args) 59 => compound_name_arguments(C, c, Args), 60 pl2r_(C, X). 61 62pl2r_(A, X), 63 compound(A) 64 => mapargs(pl2r_, A, X). 65 66pl2r_(A, X) 67 => A = X. 68 69pl2r_curly({A; B}, X) 70 => pl2r_(A, H), 71 pl2r_curly({B}, T), 72 X = [H | T]. 73 74pl2r_curly({A}, X) 75 => pl2r_(A, H), 76 X = [H]. 77 78<-(Call) :- 79 format('<- ~w~n', [Call]). 80 81<-(Var, Expr) :- 82 format('~w <- ~w~n', [Var, Expr]). 83 84:- initialization(r_init).