scryer-prolog icon indicating copy to clipboard operation
scryer-prolog copied to clipboard

Meta non-terminal calling another meta-nonterminal

Open bakaq opened this issue 1 year ago • 4 comments

This is something that I stumbled on while trying to put if__/3 from #2260 in a module. Basically, if you have a non-terminal that calls another non terminal as it's argument, module resolution doesn't work well.

%% Contents of meta_dcg.pl
:- module(meta_dcg, [test_meta//1]).

:- use_module(library(dcgs)).
:- use_module(library(format)).

:- meta_predicate(test_meta(2,?,?)).

test_meta(NT__0) -->
    call(test_meta_raw(NT__0)).
    
test_meta_raw(NT__0, Ls0, Ls) :-
    portray_clause(calling_non_terminal(NT__0)),
    phrase(NT__0, Ls0, Ls).
%% End of contents of meta_dcg.pl

%% Contents of meta_dcg_test.pl
:- use_module(library(dcgs)).

:- use_module(meta_dcg).

test -->
    [a,b,c].

case1(Ls) :-
    phrase(test_meta(test), Ls).
case2(Ls) :-
    phrase(test_meta(test_meta(test)), Ls).
case3(Ls) :-
    phrase(test_meta((
        test_meta(test),
        test
    )), Ls).
%% End of contents of meta_dcg_test.pl

?- use_module(meta_dcg_test).
   true.
?- case1(Ls).
calling_non_terminal(user:test).
   Ls = "abc".
?- case2(Ls).
calling_non_terminal(user:test_meta(user:test)).
calling_non_terminal(user:test).
   Ls = "abc".
?- case3(Ls).
calling_non_terminal(user:(test_meta(test),test)).
calling_non_terminal(test). % Unexpected, expected user:test
   error(existence_error(procedure,test/2),test/2). % Unexpected.

I think maybe this is a problem with how (',')//2 is implemented, but it may be a broader limitation of Prolog or DCGs.

bakaq avatar Jan 03 '24 03:01 bakaq

Works in SICStus. Needed to replace //1 by /3 to get rid of that warning. But then, SICStus even detected a real error in your code:

| ?- use_module(meta_dcg_test).
% compiling /home/ulrich/scryer/meta_dcg_test.pl...
! Existence error in argument 1 of use_module/1
! file library(dcgs) does not exist
! goal:  use_module(user:library(dcgs))
! Approximate lines: 2-3, file: '/home/ulrich/scryer/meta_dcg_test.pl'
%  compiling /home/ulrich/scryer/meta_dcg.pl...
%   module meta_dcg imported into user
%  compiled /home/ulrich/scryer/meta_dcg.pl in module meta_dcg, 123 msec 674048 bytes
% compiled /home/ulrich/scryer/meta_dcg_test.pl in module user, 167 msec 863616 bytes
* /home/ulrich/scryer/meta_dcg_test.pl is not a module file
yes

So that is a problem in Scryer: importing a non-module file as a module is not OK, or at least worth a warning.

UWN avatar Jan 03 '24 09:01 UWN

| ?- case1(Ls).
calling_non_terminal(user:test).
Ls = [a,b,c] ? ;
no
| ?- case2(Ls).
calling_non_terminal(user:test_meta(test)).
calling_non_terminal(user:test).
Ls = [a,b,c] ? ;
no
| ?- case3(Ls).
calling_non_terminal(user:(test_meta(test),test)).
calling_non_terminal(user:test).
Ls = [a,b,c,a,b,c] ? ;
no

UWN avatar Jan 03 '24 09:01 UWN

There is one microscopic misunderstanding here: calling_non_terminal is a bit of a misnomer. For phrase/2/3, the first argument is not a non-terminal but rather a grammar rule body. After all, think of

?- phrase([a], L),
   L = "a".

which clearly is not a non-terminal at all, but still belongs there.

UWN avatar Jan 03 '24 09:01 UWN

So that is a problem in Scryer: importing a non-module file as a module is not OK, or at least worth a warning.

Yes, when I was first learning Prolog with Scryer I found this really strange. Currently use_module/1 and consult/1 do basically the same thing, I just tend to use use_module/1 everywhere to make things more consistent, but maybe I should stop and start to make this semantic distinction.

For phrase/2/3, the first argument is not a non-terminal but rather a grammar rule body.

This is really good to know! Thanks for the explanation.

bakaq avatar Jan 03 '24 13:01 bakaq