Dict expansion issues with meta predicates

Source:

aggregate_all(count,  (member(G, Player.games), ground(G.opponent)), Count1),
aggregate_all(count,  (member(G, Player2.games), ground(G.opponent)), Count2),

Decompiled Listing:

'.'(A, games, C),
'.'(B, opponent, D),
aggregate_all(count,  (member(B, C), ground(D)), I),
'.'(E, games, G),
'.'(B, opponent, H),
aggregate_all(count,  (member(B, G), ground(H)), J),

The first switch is okayish, but the second is clearly incorrect. Is this a fixable bug?

Could be a missing meta predicate declaration, or a meta agrument specifier that is not recognized by the function expansion. The function on dict expansion should depend on meta predicate declarations. For example in my system I get:

Without aggregate_all(?,0,?) declaration:

test(Player, Count1) :-
   sys_get_obj_atomic(games, Player, A),
   sys_get_obj_atomic(opponent, G, B),
   aggregate_all(count, (member(G, A),
      ground(B)), Count1).

With aggregate_all(?,0,?) declaration:

test2(Player, Count1) :-
   aggregate_all(count, (sys_get_obj_atomic(games, Player, A),
      member(G, A),
      sys_get_obj_atomic(opponent, G, B),
      ground(B)), Count1).

Indeed, goal expansion requires appropriate declarations.

:- use_module(library(aggregate)).

t(Player2, Count2) :-
    aggregate_all(count,  (member(G, Player2.games), ground(G.opponent)), Count2).
62 ?- listing(t).
t(Player2, Count2) :-
    aggregate_all(count,
                  ( ( '.'(Player2, games, A),
                      member(G, A)
                    ),
                    '.'(G, opponent, B),
                    ground(B)
                  ),
                  Count2).

That is unfortunate, but in general meta-predicates cannot be auto-loaded reliably for this reason (all is fine if the arguments are not subject to goal expansion).

Not really sure what to do about this. One option is to stop auto loading meta-predicates. That would break quite a bit of code though while the auto loading is quite often convenient when playing around on the console. At the time auto loading was added there was no goal expansion …

You could also auto load during predictate_property/2 which gives the meta predicate information. If goal expansion then does use this information it will also work for auto loaded predicates.

I don’t have unqualified auto loading like SWI-Prolog does. But I have qualified auto loading in my system, and it seems indeed to work:

?- listing.
% user
:- use_module(library(notebook/dict)).
:- use_module(library(notebook/func)).
:- sys_auto_load(library(advanced/aggregate)).

test3(Player, Count1) :-
   advanced/aggregate:aggregate_all(count, (sys_get_obj_atomic(
         games, Player, A),
      member(G, A),
      sys_get_obj_atomic(opponent, G, B),
      ground(B)), Count1).

The sys_auto_load/1 during listing tells me that it was auto loaded already during consult, and not only during execution, since I didn’t execute it anyway.

I did not yet work on unqualified auto load for my system, but it seems to be popular, at least what the SWI-Prolog runtime itself considers.

That however would violate a later (local) definition from overruling the autoload, e.g.

p :-
    ....
   aggregate(...),
   ...

aggregate(...) :-

In this scenario the local aggregate/3 may have no relation to the library code. Two-pass compilation could help, but I’m reluctant to force that. Even then, it will only help for modules as without a module system the definition may come from a file that is loaded later.

I dunno, I only figured out just now that SWI-Prolog must also do auto load during predicate property. I assumed that it does not, but the relevant information for function expansion seems to be available:

?- predicate_property(aggregate_all(_,_,_), X).
[...]
X =  (meta_predicate aggregate_all(?, 0, -)) ;
[...]

The information seems to be available without use_module(library(aggregate)). So I don’t know whats going wrong, and why the use_module(library(aggregate)) is need in abaljeu example.

Edit 17.11.2019:
I did another test. Instead of use_module(library(aggregate)), just using aggregate_all/3, also triggers correct function expansion:

?- aggregate_all(sum(X), between(1,10,X), Y).
Y = 55.

?- [user].
test2(Player, Count1) :- 
    aggregate_all(count,  (member(G, Player.games), ground(G.opponent)), Count1).

?- listing(test2/2).
test2(A, E) :-
    aggregate_all(count,
                  ( ( '.'(A, games, B), member(C, B)),
                    '.'(C, opponent, D),  ground(D)),
                  E).

The expansion code doesn’t call predicate_property/2, but the low level thing that only inspects defined predicates.

Does predicate_property/2 get its information form the auto load index?