Library(yall) and non-optimisation

(This appears to be a difficult to reproduce problem: when I checked things a second time, the problem did not show. Also, this directive didn’t do anything: :-set_prolog_flag(optimise, true). but the -O flag did set the flag.

Anyway, in case a reproducible example can be made …

When I wrote the “deadfish challenge” code (Autum Challenge: Short Deadfish Numbers - #4 by oskardrums) I found that when I used library(yall), it ran ~10x slower, despite having the “optimise” flag on (for this particular problem, the “optimise” flag resulted in a ~10% performance improvement).

When I looked at the generated code (using vm_list/1), I noticed that the auxiliary predicates were as expected, except that they also had something like this before the byte codes:

0 s_trustme(clause(95761178407712))

for the auxiliary for [S0,S]>>(S is S0+1). This didn’t appear for the equivalent incr(X0,X):-X is X0+1, nor did it appears when “optimise” wasn’t set.

The sample code is here: deadfish code using dict/DCG and library(yall) · GitHub
It has an if directive to switch between using library(yall) and regular Prolog code.

I think its a caching problem of library(yall). If you use
the same closure multiple times, it generates only one aux,
whereas after a optimise flag change, it should generate multiple aux.

Test case to reproduce the problem:

:- set_prolog_flag(optimise, true).
test :- maplist([S0,S]>>(S is S0+1), [1,2,3], _).
:- set_prolog_flag(optimise, false).
test2 :- maplist([S0,S]>>(S is S0+1), [1,2,3], _).

Now do a listing:

?- listing(test/0), listing(test2/0).
test :-
    maplist('__aux_yall_956d127e8aef66cd7d31d334aa76007244004c4a',
            [1, 2, 3],
            _).

test2 :-
    maplist('__aux_yall_956d127e8aef66cd7d31d334aa76007244004c4a',
            [1, 2, 3],
            _).

Twice the same auxiliary predicate.

Edit 07.10.2023
Its this feature:

Note that in some cases multiple expansions of similar goals can share the same compiled auxiliary predicate. In such cases, the implementation of goal_expansion/2 can use predicate_property/2 using the property defined to test whether the predicate is already defined in the current context.
SWI-Prolog -- compile_aux_clauses/1

Used in library(yall) here:

compile_aux_clause_if_new(Head, Lambda) :-
      prolog_load_context(module, Context),
      (   predicate_property(Context:Head, defined)
      ->  true
      ;   expand_goal(Lambda, LambdaExpanded),
          compile_aux_clauses([(Head :- LambdaExpanded)])
      ).

The optimize flag is unrelated AFAIK (well, only a little by removing unneeded true and fail goals and branches). What matters is whether library(yall) is loaded and compiled by its goal expansion rules or it is dynamically called. As dynamically calling implies a lot of term copying, this is much slower. If you look back at older posts you’ll also see that the semantics differ wrt variables shared between the clause and the lambda expression.

Possibly we should remove library(yall) from the autoload system such that it needs to be loaded explicitly for all usage?

Ah, the auto-loading explains why I had “non-deterministic” effects (presumably the s_trustme is an artiifact of dynamic calls?)

I vote for not auto-loading library(yall), although that would undoubtedly break some existing code (easily fixed) – there are the dynamic vs static issues and also I’ve seen some strange error messages when I’ve inadvertently triggered auto-loading of library(yall), when I made a typing mistake in an arithmetic expression using / or >>.

Another possibility is to first deprecate the fact that library(yall) is autoloaded for a couple of versions, and actually disable its autoloading in at some further point in the future. This deprecation would be accompanied with some indication/warning for autoloaded usage of library(yall), for example by painting lambda terms orange in your IDE unless you explicitly require library(yall), or by emitting a warning during compilation. That might be more friendly for people that already rely on library(yall) being autoloaded, WDYT?

The other point of view is that the semantic differences are in fact a bug; and the sporadic differences that @peter.ludemann reported are also a bug; and disabling autoloading is at least a work-around.

But I admit that this is a bit extreme.

(After the initial enthusiasm I stopped using library(yall) because of a couple of frustrating debugging sessions, so I am maybe not the best person to give opinions :slight_smile: )

AFAIK, this supervisor code is generated for static predicates that have only one clause.

I think I agree with @oskardrums to (first) issue a warning. Seems we need to add a list of libraries that are better not autoloaded to the autoloader. Those are libraries that use term/goal expansion.

1 Like

For a start, I added a Prolog flag warn_autoload that warns if a predicate is autoloaded from a file that also defines global goal- or term-expansion. That triggers quite some stuff. I fixed many of them, notably calls to debug/3 that defines goal_expansion/2 to remove these calls in optimized mode.

Please enable the flag and see whether it does what we want. Once most warnings that it produces are silenced we should enable the flag by default.

For now:

?- set_prolog_flag(warn_autoload, true).
?- maplist([In,Out]>>atom_concat(In,'_p',Out), [a,b], ListOut).
Warning: Auto-loading (>>)/4 from library(yall) into module user is deprecated due to term- or goal-expansion
ListOut = [a_p, b_p].

The warn_autoload broke one of my tests, but there wasn’t much output to indicate what had gone wrong when I ran it in Emacs’ “compilation” window. The test ran a .plt file with --on-warning=status, which gave an error return code and Warning: Halting with status 1 due to 0 errors and 1 warnings. When I changed the --on-warning=status to --on-warning=print, I got the normal output, and when I changed to --on-warning=halt, it stopped part-way through printing one of the progress messages.

So, I’m guessing that plunit disables the warning message when I run in a non-tty window … when I ran it under the Emacs shell, with set_prolog_flag(autoload, false), I got messages that helped me figure out the problem.

One more error whose cause I haven’t yet figured out:

ERROR: /home/peter/.local/lib/swipl/library/listing.pl:102:
ERROR:    term_expansion/2: Unknown procedure: error:must_be/2

By default, the current test framework collects the output and discards it if the test succeeds. A warning doesn’t change the success. You can use run_tests(all, [format(log)]). to get all output, which is default if the output is not a tty. I think the unit test framework should listen to the flag associated with --on-warning=status and emit warnings if this flag is set.

Haven’t seen that. Is that associated with set_prolog_flag(autoload, false)? If so, some dependency is missing, either in one of the libraries or in your code.

I’m getting this strange warning message when I run help/1 and it processes the source:

Warning: /home/peter/src/pykythe/pykythe/module_path.pl:304:
Warning:    Auto-loading re_matchsub/4 from library(pcre) into module '$xref_tmp' is deprecated due to term- or goal-expansion

I have :- use_module(library(pcre), [re_matchsub/4, re_replace/4])., so this shouldn’t be happening.

I got similar warnings for goals that called re_replace/4, but the warnings went away when I changed the call to pcre:re_replace(...).