Clause/2 gives different results when library(clpfd) is loaded

Consider this declaration, and the related query:

example(Lss) :-
    maplist(member(3), Lss).

%?- Term = example(X), clause(Term, Body).
%@ Term = example(X),
%@ Body = maplist(member(3), X).

But now, if I also load library(clpfd) I get:

:- use_module(library(clpfd)).

example(Lss) :-
    maplist(member(3), Lss).

%?- Term = example(X), clause(Term, Body).
%@ Term = example(X),
%@ Body = '__aux_maplist/2_member+1'(X, 3).

As you can see, the result changes, and the clause is read as __aux_maplist instead. This is a problem for me because I’m writing meta-interpreters for typing some of my code using clause/2, and the fact that the result changes based on what modules are imported was totally inscrutable to me!

How would you solve this problem? Why is library(clpfd) influencing unrelated code? Can I isolate different concerns of my code in a better way? Is this documented anywhere?

1 Like

That looks to me like library(apply_macros) is being loaded, which does that sort of source transform.

1 Like

library(clpfd) (and several others) load library(apply_macros), which optimizes certain meta predicates. I’m not really sure how we should handle this. It should not affect meta-interpreters as the clauses in the DB are still nice and correct Prolog that is even simpler than the original.

Just making it work for the library that loads library(apply_macros) would be an option. The disadvantage is that a common usage scenario is to load this library and be sure that all these simple meta calls are compiled away.

Most Prolog systems won’t even allow to get the code for static predicates. This would suggest not to apply this expansion for dynamic code and have some option to load a file as all dynamic. I’m not sure what the value of that is either.

1 Like

Thanks @jamesnvc and @jan for pointing out that the rewrite is introduced in library(apply_macros).

I guess the documentation is here, but there’s no mention of library(yall) and yet:

:- use_module(library(apply_macros)).

example2(As) :-
    L = [1,2,3],
    maplist({L}/[X]>>member(X,L), As).

%?- clause(example2(_), Body).
%@ Body =  (_13262=[1, 2, 3], '__aux_maplist/2___aux_yall_0acee418088eabf60688ed3721777c91323f1885+1'(_12856, _13262)).

And this introduces another problem: while in my original question I could maybe parse the functor of '__aux_maplist/2_member+1'(X, 3), now I’m unsure what to do with the 0acee... part of the yall.

Notice also that this is becoming the implementation of a grammar for functor names for which I don’t have a spec (yall doesn’t seem even mentioned in apply_macros!).

@jan could you elaborate on your suggestion in this case? I’m not sure I get it! Ideally, I shouldn’t care about these optimization for this meta-interpreter, and I would like to just access the code I actually wrote.

But that’s not what you’re suggesting, right?

library(yall) doesn’t use library(apply_macros) … it works by creating new predicates that contain the “lambda” definitions. This is separate from library(apply_macros), which expands out a specific set of predicate goals – in “apply macros”, “apply” isn’t a verb; the name means “expand (macros) from library(apply)”.

@peter.ludemann thanks! But if library(yall) doesn’t use library(apply_macros) why do I have this different behaviors:

Without library(apply_macros):

example2(As) :-
    L = [1,2,3],
    maplist({L}/[X]>>member(X,L), As).

%?- clause(example2(_), Body).
%@ Body =  (_6040=[1, 2, 3], maplist({_6040}/[_6062]>>member(_6062, _6040), _5634)).

With library(apply_macros):

:- use_module(library(apply_macros)).

example2(As) :-
    L = [1,2,3],
    maplist({L}/[X]>>member(X,L), As).

%?- clause(example2(_), Body).
%@ Body =  (_13262=[1, 2, 3], '__aux_maplist/2___aux_yall_0acee418088eabf60688ed3721777c91323f1885+1'(_12856, _13262)).

Also, I’m still not sure on which is the advice I should follow when I want to interpret my code.

I think that library(yall) provides an “interpreted” version of >>/2 for situations where its term expansion misses something – for example, as a closure passed to a meta-predicate. When library(apply_macros) is used, it expands the maplist/2 call and that allows library(yall)'s term expansion to work.
(This is an educated guess – I’m too lazy to look inside the two libraries to see the details of how they work.)

The maplist/2 expansion is a requirement to do the yall code expansion. Note that the yall code expansion is a complicated thing. Earlier messages here showed the scoping difference between interpreted and compiled yall lambda expressions.

Still, the problem remains: “why do you care”?