`message_hook` dropping messages during `xref_source`

I’m trying to capture swipl’s error messages (specifically import_private(_,_), attempting to import from a module a predicate not exported by that module) via message_hook/3.

This is work for the LSP, and we call xref_clean(P), xref_source(P) on a module path after setting up message_hook to capture messages like singletons or syntax errors.

If I set up the hooks and run ['path/to/file.pl']. from the REPL I see all the messages I’d expect, including import_private(_,_). But calling the xref predicates I don’t see that message captured.

Is there some xref option that I would need to set in order to capture all messages?

:- module(intercept, []).

:- multifile user:message_hook/3.
:- dynamic user:message_hook/3.

user:message_hook(A, warning, C) :-
    format('[WARNING]>>> ~p - ~p~n', [A,C]).
user:message_hook(A, error, C) :-
    format('[ERROR]>>>>> ~p - ~p~n', [A,C]).

% intercept: 1 ?- ['test/checking_input1.pl'].
% [WARNING]>>> import_private(user,clpfd:asdfasdfasdfasdf/2) - ['import/1: ~p is not exported (still imported into ~q)'-[clpfd:asdfasdfasdfasdf/2,user]]
% [ERROR]>>>>> error(existence_error(source_sink,library(does_not_exist)),_11888) - ['~w `~p\' does not exist'-[source_sink,library(does_not_exist)]]
% [WARNING]>>> goal_failed(directive,user:use_module(library(does_not_exist))) - ['Goal (~w) failed: ~p'-[directive,user:use_module(library(does_not_exist))]]
% [ERROR]>>>>> error(existence_error(source_sink,nexiste_pas),_12938) - ['~w `~p\' does not exist'-[source_sink,nexiste_pas]]
% [WARNING]>>> goal_failed(directive,user:use_module(nexiste_pas,[pred/2])) - ['Goal (~w) failed: ~p'-[directive,user:use_module(nexiste_pas,[pred/2])]]
% [WARNING]>>> singletons((foo(_13610):-_13914,_13610=1,_13752{a:_13754},[1,2,3|_13838]),['Gae','B','Z']) - ['Singleton variables: ~w'-[['Gae','B','Z']]]
% [ERROR]>>>>> error(type_error(callable,(_14918,_14930=1,_14942{a:_14944},[1,2,3|_14964])),context(system:'$record_clause'/3,_14970)) - ['Type error: `~w\' expected, found `
% ~p\''-[callable,(_14918,_14930=1,_14942{a:_14944},[1,2,3|_14964])],' (~w ~w)'-[a,compound]]
% [ERROR]>>>>> error(syntax_error(operator_expected),file('c:/users/me/appdata/local/swi-prolog/pack/lsp_server/test/checking_input1.pl',14,12,205)) - [url('c:/users/me
% /appdata/local/swi-prolog/pack/lsp_server/test/checking_input1.pl':14:12),': ','Syntax error: ','Operator expected']
% true.
%
% intercept: 2 ?- P = 'test/checking_input1.pl', xref_clean(P), xref_source(P).
% [WARNING]>>> error(existence_error(file,library(does_not_exist)),_8110) - ['~w `~p\' does not exist'-[file,library(does_not_exist)]]
% [WARNING]>>> error(existence_error(file,nexiste_pas),_9042) - ['~w `~p\' does not exist'-[file,nexiste_pas]]
% [WARNING]>>> singletons((foo(_9388):-_9692,_9388=1,_9530{a:_9532},[1,2,3|_9616]),['Gae','B','Z']) - ['Singleton variables: ~w'-[['Gae','B','Z']]]
% [ERROR]>>>>> error(syntax_error(operator_expected),file('c:/users/me/appdata/local/swi-prolog/pack/lsp_server/test/checking_input1.pl',14,12,205)) - [url('c:/users/me
% /appdata/local/swi-prolog/pack/lsp_server/test/checking_input1.pl':14:12),': ','Syntax error: ','Operator expected']
% P = 'test/checking_input1.pl'.

Sorry for the late response. Could it be that you are calling xref_source/2 using the silent(true) option? That is what happens for example in the built-in editor integration.

You may also want to use thread_message_hook/3 instead of message_hook/3 to just locally and temporarily collect messages.

1 Like

Thanks for following up! I tried calling xref_source(Path, [silent(false)]) and am getting the same results. (I also tried replacing message_hook with thread_message_hook in case that was the problem, however there was no difference in my example. But thanks, I’ll pass that recommendation on to the maintainer jamesnvc)

I didn’t realize there was already an editor using xref for diagnostics! Could you point me to where in the code-base the built-in editor (is that SWISH?) uses xref? Maybe I’ll see what I’m doing wrong.

1 Like

It is used by library(prolog_colour), which is used by the built-in editor, SWISH and Thinker. It silences messages though. Instead, it uses the cross-referencer information to indicate where predicates/… come from or to detect they do no exist. Can you give a small test file and calls to reproduce your problem?

The test setup I’ve been using:

% private.pl
:- use_module(library(clpfd), [does_not_exist/0]).
:- module(intercept, []).

:- multifile user:thread_message_hook/3.
:- dynamic user:thread_message_hook/3.

user:thread_message_hook(Term, Kind, Lines) :-
    memberchk(Kind, [error, warning]),
    format('[~w]>>> ~p - ~p~n', [Kind, Term, Lines]).

load(Silent) :-
    P = 'private.pl',
    xref_clean(P),
    xref_source(P, [silent(Silent)]).

% 1 ?- intercept:load(false).
% true.
% 
% 2 ?- intercept:load(true).  
% true.
% 
% 3 ?- ['private.pl'].
% [warning]>>> import_private(user,clpfd:does_not_exist/0) - ['import/1: ~p is not exported (still imported into ~q)'-[clpfd:does_not_exist/0,user]]
% true.

I’m wondering if the problem is that the import_private warning is only generated when a use_module directive is actually executed, and that xref_source doesn’t attempt to “load” modules as dynamically as use_module. Like, maybe xref considers checking imported predicates to be a runtime task instead of a static analysis one?

I’ll look into library(prolog_color), thanks for the pointer :folded_hands:

1 Like