Simple term_expansion debugging

When a term passes through term_expansion/2 trying to debug/understand the term expansion can be challenging at first.

One effective aid in debugging term_expansion/2 is using debug/3 with listing/1.

Here is a very simple module with term_expansion/2 and debug/3.

Note: This is in a file C:/directories/simple_rewrite_example.pl.

:- module( simple_rewrite, [
    op(1200, xfx, '::=')
]).

user:term_expansion((H::=T), (H:-T)) :-
    debug(rewrite_topic,'::= rewrite rule applied.',[]).

It simply takes a term written using ::= and rewrites it with :-.

And here is a very simple module with a predicate containing ::=

:- module(example_module,
    [
        a_predicate/0
    ]).

:- use_module('C:/directories/simple_rewrite_example.pl').

a_predicate ::=
    Value = 1,
    Value == 2.

Normally when a predicate is listed, e.g.

?- listing(a_predicate).
example_module:a_predicate :-
    Value=1,
    Value==2.

no debug messages are printed.

If the debug topic is enabled, e.g.

?- debug(rewrite_topic).
Warning: rewrite_topic: no matching debug topic (yet)
true.

and then the same predicate is listed, e.g.

?- listing(a_predicate).
% ::= rewrite rule applied.
example_module:a_predicate :-
    Value=1,
    Value==2.

the debug message appears.

While this is a very simple example its effectiveness is easily amplified by adding more debug/3 calls.


Also see this related post: Sharing my debugging message discovery


Here is an example of the messages when a single predicate is expanded with the library(edcg) using a custom version of library(edcg) with copious debug/3 calls.

?- debug(edcg).
Warning: edcg: no matching debug topic (yet)
true.

?- listing(called_07).
% Expanding called_07(_312)
% _new_goal - entry - Goal:called_07(_312), GList:[acc_07], GArity:_3362, TGoal:_846
% _new_goal - exit  - Goal:called_07(_312), GList:[acc_07], GArity:1
                     TGoal:called_07(_312,_3460,_3462)
% _create_acc_pass - recursive 1 - entry - A:acc_07, AList:[], Index:1, TGoal:called_07(_312,_3460,_3462), LeftA:_3576, RightA:_3578, Acc:_3570, Pass:_3630
% _create_acc_pass - base 1
% _create_acc_pass - recursive 1 - exit  - A:acc_07, AList:[], Index:1, TGoal:called_07(_312,_3460,_3462), LeftA:_3460, RightA:_3462, Acc:[], Pass:[]
% _expand_goal - recursive 1 - entry - (G1,G2) - G1:_328/acc_07, G2:[_380]:acc_07,acc_07/_380,{format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380])}, TG1:_3924, TG2:_3926, NaAr:called_07/1, HList:[acc_07], Acc:[acc(acc_07,_3460,_3462)], NewAcc:_3972, Pass:[]
% _expand_goal - base 8 - (X/A) - exit  - X:_328, A:acc_07, Acc:[acc(acc_07,_328,_3462)]
% _expand_goal - recursive 1 - entry - (G1,G2) - G1:[_380]:acc_07, G2:acc_07/_380,{format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380])}, TG1:_4166, TG2:_4168, NaAr:called_07/1, HList:[acc_07], Acc:[acc(acc_07,_328,_3462)], NewAcc:_3972, Pass:[]
% _expand_goal - base 6 - (L:A) - exit  - L:[_380], A:acc_07, Joiner:_328=_380,true, NaAr:called_07/1, Acc:[acc(acc_07,_328,_3462)], NewAcc:[acc(acc_07,_4328,_3462)]
% _expand_goal - recursive 1 - entry - (G1,G2) - G1:acc_07/_380, G2:{format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380])}, TG1:_4460, TG2:_4462, NaAr:called_07/1, HList:[acc_07], Acc:[acc(acc_07,_4328,_3462)], NewAcc:_3972, Pass:[]
% _expand_goal - base 10 - (A/X) - exit  - A:acc_07, X:_380, Acc:[acc(acc_07,_4328,_380)]
% _expand_goal - base 1 - {G} - exit  - G:format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380]), Acc:[acc(acc_07,_4328,_380)]
% _expand_goal - recursive 1 - exit  - (G1,G2) - G1:acc_07/_380, G2:{format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380])}, TG1:true, TG2:format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380]), NaAr:called_07/1, HList:[acc_07], Acc:[acc(acc_07,_4328,_380)], NewAcc:[acc(acc_07,_4328,_380)], Pass:[]
% _expand_goal - recursive 1 - exit  - (G1,G2) - G1:[_380]:acc_07, G2:acc_07/_380,{format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380])}, TG1:_328=_380,true, TG2:true,format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380]), NaAr:called_07/1, HList:[acc_07], Acc:[acc(acc_07,_328,_380)], NewAcc:[acc(acc_07,_4328,_380)], Pass:[]
% _expand_goal - recursive 1 - exit  - (G1,G2) - G1:_328/acc_07, G2:[_380]:acc_07,acc_07/_380,{format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380])}, TG1:true, TG2:(_328=_380,true),true,format(Value: ~w, A: ~w, B: ~w~n,[_312,_328,_380]), NaAr:called_07/1, HList:[acc_07], Acc:[acc(acc_07,_328,_380)], NewAcc:[acc(acc_07,_4328,_380)], Pass:[]
% _finish_acc - recursive 1 - entry - Link:_380,Acc:[]
% _finish_acc - base 1
% _finish_acc - recursive 1 - exit  - Link:_380,Acc:[]
edcg_example:called_07(Value, A, B) :-
    true,
    A=B,
    true,
    true,
    format('Value: ~w, A: ~w, B: ~w~n', [Value, A, B]).

true.
4 Likes

The other tip: if goal/term expansion doesn’t do what you want, just call it explicitly using the term you want to see expanded. That way you can easily trace it the usual way.

Yes that was the approach I originally tried with EDCG but the problem I ran into and am still unable to solve is that EDCG has some initialization facts that are used by the predicates using term_expansion, e.g.

edcg:acc_info(acc_04, Value, In, _, In = Value ).

edcg:pred_info(called_04,1,[acc_04]).

Here is an entire example.

:- module(edcg_example,
    [
        caller_04/0
    ]).

:- use_module(library(edcg)).

edcg:acc_info(acc_04, Value, In, _, In = Value ).

edcg:pred_info(called_04,1,[acc_04]).

caller_04 :-
    called_04(Value,A,B).

called_04(Value) -->>
    A/acc_04,
    [B]:acc_04,
    { format('Value: ~w, A: ~w, B: ~w~n',[Value,A,B]) }.

I have yet to figure out how to setup a test or a trace when these initialization facts are needed.

Not expecting an answer as I am having to learn how SWI-Prolog works internally but if an answer is given then will know when I am headed in the right direction.


EDIT

The problem of using trace/0 or gtrace/0 with initialization facts seems to be resolvable with

  1. Consult the file as normal which will load the initialization facts
  2. Then call term_expansion/2 on the term. In other words, rerunning the term expansion on a clause should not change the database.

For the problem of adding test cases my current hypotheses is that since EDCG was written without the knowledge and use of modules and begin_tests/1 creates a module, so EDCG does not see the code in a test as a separate module and thus the initialization facts are not seen as being unique to each module/test. The solution the code seems to be asking for is to be redesigned to work with modules and thus by extension should work with test book-ended by begin_tests and end_tests.

Given that the “initialization facts” are clauses for multifile predicates, they are shared and never “unique to each module/test”. As I mentioned a couple of times, the use of multifile predicates in the port/implementation of EDCGs is flawed: two modules defining EDCGs that happen to use e.g. accumulators with the same name but different definitions can clash as the expansion code calls a multifile predicate and not necessarily the one defining in the module being expanded. Not that the EDCGs port is unique in SWI-Prolog ecosystem having this flaw…

P.S. The Logtalk port of EDCGs doesn’t use multifile predicates and its alternative expansion solution could also be used in the SWI-Prolog port.

2 Likes

It seems that logtalk uses module-local predicates acc_info/{5,7},pred_info/3, and pass_info/{1,2}. I can see that pred_info/3 makes sense for being module-local; but what about acc_info/5 that’s the same for multiple modules?

Object-local, not module-local. :stuck_out_tongue: You have a minor typo in your reply: acc_info/{5,5} should be acc_info/{5,7}.

Not sure I understand your question, however. All those predicates are used in the expansion of an EDCG. Even if, in some particular case, some of them are shared between objects or modules, there are solutions to share them and avoid repetition. But that doesn’t mean that they should be global, which is what we get with the predicates being declared multifile and the consequent risk of clashes.

1 Like

(Fixed the typo)

Multiple modules/objects could use the same accumulators … would you simply put the acc_info{5,7} into its own module (presumably with the accumulator predicate) and then import it wherever used? (The pred_info predicates would be “object-local”.)

In my current port, importing (from a module) will not work as the clauses need to be local in order to be term-expanded. Predicates that are visible locally due to an import are not visible to the term-expansion mechanism as they are not part of the source file being expanded. A sharing solution that will work, albeit low-level, would be to use an include/1 directive.

Note that there is a fundamental difference here between SWI-Prolog and Logtalk. In SWI-Prolog, clauses are available for use as soon as they are compiled as it uses a single stage compiler. But Logtalk uses a multi stage compiler and the predicates that define e.g. accumulators are only available for calling after the source file is compiled and loaded. But an alternative edcg module should be able to use the import solution you suggest. You can use the prolog_load_context/2 predicate to find which module you are compiling in order to call the predicates in that module without requiring them to be multifile.

Jan W. has some useful details here.