Writing macros in SWI-Prolog
Asked Answered
R

2

8

I am trying to implement a simple macro for switch-statements in SWI-Prolog.

This is a series of conditional statements:

(X = a ->
    Output = case1;
X = b ->
    Output = case2;
X = c ->
    Output = case3).

and this is an equivalent (but much slower) expression with the same effect:

switch(X, [
    a : (Output = case1),
    b : (Output = case2),
    c : (Output = case3)
])

I have used many predicates like this one in an application, but this slows it down considerably. Is it possible to implement this switch predicate as a macro so that it will be changed into a normal conditional expression at compile-time, to improve the application's performance?

Regeneracy answered 16/6, 2016 at 18:29 Comment(4)
The fastest way will likely not be even a series of if-then-elses, but rather a set of clauses for each case. Additional advantage: You will be able to use these clauses in more directions. Check out term_expansion/2 and goal_expansion/2. To rewrite terms at compilation time. See SWI-Prolog's maplist/2 in library(apply_macros) to see how one can compile such constructs to calls of auxiliary predicates.Certainty
There is already a way to do exactly what you describe: a predicate with multiple clauses, where the first argument is the "switch" expression (as @Certainty also points out....). Why are you discarding this idiomatic, widely used construct?Cozenage
PS. If the question is actually about how to do expansion at compile time, than it is indeed a different question.Cozenage
@Boris Yes, that is what the question is about.Regeneracy
H
4

a minimal attempt: create a file named switch.pl

:- module(switch, []).

compile_caselist(X, [K:Clause], (X = K -> Clause)) :- !.
compile_caselist(X, [K:Clause|CaseList], ((X = K -> Clause);Translated)) :-
    compile_caselist(X, CaseList, Translated).

:- multifile user:goal_expansion/2.
user:goal_expansion(F, G) :-
    F = switch(X, CaseList),
    compile_caselist(X, CaseList, G).

then use it like as usual: for instance, in a file switch_test.pl

:- use_module(switch).

test1(X) :-
    X = a -> writeln(case1) ;
    X = b -> writeln(case2) ;
    X = c -> writeln(case3).

test2(X) :-
    switch(X, [
           a : writeln(case1),
           b : writeln(case2),
           c : writeln(case3)
       ]).

after compilation of switch_test.pl:

?- listing(test2).
test2(A) :-
    (   A=a
    ->  writeln(case1)
    ;   A=b
    ->  writeln(case2)
    ;   A=c
    ->  writeln(case3)
    ).

true.

edit due to multiple requests, here is a compilation schema to separate clauses:

:- module(switch, []).

:- multifile user:term_expansion/2.
user:term_expansion((H:-B), [(H:-T)|SWs]) :-
    collect_switches(H,B,T,SWs),
    SWs \= [],
    debug(switch, 'compiled <~w>~nto <~w>~nwith <~w>', [H,T,SWs]).

collect_switches(H,(A0;A),(B0;B),SWs) :-
    collect_switches(H,A0,B0,S0),
    collect_switches(H,A,B,S),
    append(S0,S,SWs).

collect_switches(H,(A0,A),(B0,B),[S|SWs]) :-
    call_switch(H,A0,B0,S), !,
    collect_switches(H,A,B,SWs).
collect_switches(H,(A0,A),(A0,B),SWs) :-
    collect_switches(H,A,B,SWs).
collect_switches(H,A,B,[S]) :-
    call_switch(H,A,B,S), !.
collect_switches(_,C,C,[]).

call_switch(H,switch(X,CL),call(G,X),CTs) :-
    functor(H,F,A),
    R is random(1000000),
    format(atom(G), '~s_~d_~d', [F,A,R]),
    maplist({G}/[K:C,(H:-C)]>>(H=..[G,K]),CL,CTs).

now the test script has been wrapped in a module, to ease further listing:

:- module(switch_test, [test1/1,test2/1]).
:- use_module(switch).

test1(X) :-
    X = a -> writeln(case1) ;
    X = b -> writeln(case2) ;
    X = c -> writeln(case3).

test2(X) :-
    switch(X, [
           a : writeln(case1),
           b : writeln(case2),
           c : writeln(case3)
       ]).

and the result, after compiling switch_test.pl:

?- switch_test:listing.

test1(A) :-
    (   A=a
    ->  writeln(case1)
    ;   A=b
    ->  writeln(case2)
    ;   A=c
    ->  writeln(case3)
    ).

test2(A) :-
    call(test2_1_362716, A).

test2_1_362716(a) :-
    writeln(case1).
test2_1_362716(b) :-
    writeln(case2).
test2_1_362716(c) :-
    writeln(case3).

to ease debugging:

?- debug(switch).

that outputs a message like this when compiling:

% [Thread pq] compiled <test2(_G121946)>
to <call(test2_1_362716,_G121946)>
with <[[(test2_1_362716(a):-writeln(case1)),(test2_1_362716(b):-writeln(case2)),(test2_1_362716(c):-writeln(case3))]]>

note: this sketch obviously is very likely to need more testing.

If you decide to benchmark the improvements (if any), please don't use IO statements (like writeln), since those would dominate anyway the execution timings.

Hein answered 16/6, 2016 at 20:20 Comment(6)
This still looks horribly wasteful. Why not expand to individual clauses instead?Cozenage
@Boris: there are problems to compile to individual clauses, I think... for instance, pass around the context, or dreaming up an appropriate unique name. Surely doable, but not in a short answer, that aims primarily to be on point wrt OP's (very precise) questionHein
@Hein Would it be possible to automatically expand switch([a:b,c:d]). into multiple clauses like case(a,b). case(c,d).?Regeneracy
@AndersonGreen It is possible, but I think that would be another question. You would have to explain why writing it as case(a,b). case(c,d) is not good. You could create the name using term_hash/2 (read the comment at the bottom of the link! and also look at the implementation of library(apply_macros)).Cozenage
Very nice work, thank you for posting this! collect_switches/4 seems a good candidate for using a DCG instead.Certainty
It might also be possible to solve this problem using a partial evaluator for Prolog.Regeneracy
C
2

I hope you are using the writeln above only for demonstration purposes. Here is the idiomatic way to write the same program as in your question:

foo(a, case1).
foo(b, case2).
foo(c, case3).

And this is what this program does:

?- foo(a, X).
X = case1.

?- foo(X, case1).
X = a.

?- foo(X, Y).
X = a,
Y = case1 ;
X = b,
Y = case2 ;
X = c,
Y = case3.

Important points:

  • No need for writeln, the top level does that (if you really need to write to output, you can of course do this, but it wouldn't hurt to keep it separate from the rest of the logic).
  • This is definitely more space and time efficient that any of the other suggestions
  • You can enumerate your cases when the switch expression is a variable

Is it possible that you did not fully understand this answer to this question of yours?.

Note that if you can do everything in the head of the predicate, you don't even need the predicate body: again, see that same answer and my example.

You seem to discard this suggestion because of the number of arguments, but I fail to see how any other solution will solve that problem. Can you demonstrate in your question how you would like to write your switch statement, exactly, when more arguments are involved?

One more thing: if you have a lot of cases, it can be easier to indeed write them in a list; then, you can use term expansion to add a table to your database at compile time. See this question and the term_expansion example towards the end of this answer; the example is a verbatim copy from the SWI-Prolog documentation (look at the bottom of that page). You could use goal_expansion instead of term_expansion of course.

Cozenage answered 17/6, 2016 at 13:14 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.