scryer-prolog
scryer-prolog copied to clipboard
Lambda with a predicate: existence error after "two unifications"
Loading lambda and, for example, lists library:
$ scryer-prolog -f
?- use_module(library(lambda)).
true.
?- use_module(library(lists)).
true.
Through "one unification", so to speak, as expected:
?- Lambda = \N^length("",N), call(Lambda,N).
Lambda = \0^length([],0), N = 0.
The unexpected existence error examples:
?- [Lambda] = [\N^length("",N)], call(Lambda,N).
error(existence_error(procedure,length/2),length/2).
?- Lambda = \N^length("",N), Pred = Lambda, call(Pred,N).
error(existence_error(procedure,length/2),length/2).
But, for example, this works as expected:
?- [Lambda] = [\N^(N=1)], call(Lambda,N).
Lambda = \1^(1=1), N = 1.
?- Lambda = \N^(N=1), Pred = Lambda, call(Pred,N).
Lambda = \1^(1=1), N = 1, Pred = \1^(1=1).
PS: It's not about the lists library, I could consult my own file with my own predicate in a lambda expression used in this way with the same "existence error" effect.
Probably related to #2255.
In SICStus, the existence error also indicates the module where that error occurs.
Could you disassemble the WAM code just to see what has been compiled there?
:- use_module(library(lambda)).
:- use_module(library(lists)).
:- use_module(library(diag)).
% ?- test1.
% true.
test1 :-
Lambda = \N^length("",N),
call(Lambda,N).
% ?- test2.
% error(existence_error(procedure,length/2),length/2).
test2 :-
Lambda = \N^length("",N),
Pred = Lambda,
call(Pred,N).
test1: The "as expected" case:
?- wam_instructions(test1/0,Instrutions);false.
% [...]
Instrutions =
[allocate(1),
put_variable(x(1),1),
put_structure(length,2,x(3)),
set_constant([]),
set_variable(y(1)),
put_structure(^,2,x(4)),
set_value(y(1)),
set_value(x(3)),
put_structure(\,1,x(2)),
set_value(x(4)),
call(=,2),
put_structure(length,2,x(3)),
set_constant([]),
set_value(y(1)),
set_constant('$index_ptr'(6800)),
put_structure(:,2,x(4)),
set_constant(user),
set_value(x(3)),
put_structure(^,2,x(3)),
set_value(y(1)),
set_value(x(4)),
set_constant('$index_ptr'(19275)),
put_structure(:,2,x(4)),
set_constant(user),set_value(x(3)),
put_structure(\,1,x(3)),
set_value(x(4)),
set_constant('$index_ptr'(19371)),
put_structure(:,2,x(1)),
set_constant(user),
set_value(x(3)),
put_value(y(1),2),
deallocate,
execute(call,2)]
; false.
test2: The "existence error" case:
?- wam_instructions(test2/0,Instrutions).
Instrutions =
[allocate(3),
put_variable(y(1),1),
put_structure(length,2,x(3)),
set_constant([]),
set_variable(y(2)),
put_structure(^,2,x(4)),
set_value(y(2)),
set_value(x(3)),
put_structure(\,1,x(2)),
set_value(x(4)),
call(=,2),
put_variable(y(3),1),
put_value(y(1),2),
call(=,2),
put_unsafe_value(3,1),
put_value(y(2),2),
deallocate,
execute(call,2)].
Any easy way to tell what module we are in? (I hoped it would show here, but this set_constant('$index_ptr'(19371)), is obscure.)
Any easy way to tell what module we are in?
I'm sorry, everything I know is here. I did not explicitly defined any module, I only loaded the file with the predicates test1/0 and test2/0 from the command line.
The documentation of library(diag) shows how to decompile inlined predicates indicated by code offsets, using inlined_instructions/2: https://www.scryer.pl/diag
I'm sorry. I'm only a naive user, not the right person to understand things here...
?- inlined_instructions(6800, Is),maplist(portray_clause, Is).
try_me_else(66).
allocate(6).
get_variable(y(1),2).
get_level(y(2)).
get_variable(x(3),1).
put_variable(y(3),1).
put_value(y(1),2).
put_variable(y(4),4).
call('$skip_max_list',4).
cut(y(2)).
try_me_else(10).
get_prev_level(y(5)).
put_value(y(4),1).
put_constant(level(shallow),[],x(2)).
call(==,2).
cut(y(5)).
put_value(y(1),1).
put_unsafe_value(3,2).
deallocate.
execute(=,2).
retry_me_else(15).
get_prev_level(x(3)).
call(nonvar,1,y(4)).
cut(x(3)).
call(var,1,y(1)).
put_value(y(4),1).
put_list(level(shallow),x(2)).
set_void(2).
call(=,2).
put_constant(level(shallow),finite_memory,x(1)).
put_structure(/,2,x(2)).
set_constant(length).
set_constant(2).
deallocate.
execute(resource_error,2).
retry_me_else(11).
get_prev_level(x(3)).
call(nonvar,1,y(1)).
cut(x(3)).
put_variable(y(5),1).
sub(y(1),y(3),1).
call(is,2).
put_unsafe_value(4,1).
put_value(y(5),2).
deallocate.
execute(length_rundown,2).
retry_me_else(14).
get_prev_level(y(6)).
put_value(y(1),1).
put_value(y(4),2).
call(==,2).
cut(y(6)).
put_value(y(4),1).
call(failingvarskip,1).
put_constant(level(shallow),finite_memory,x(1)).
put_structure(/,2,x(2)).
set_constant(length).
set_constant(2).
deallocate.
execute(resource_error,2).
trust_me(0).
put_unsafe_value(4,1).
put_value(y(1),2).
put_unsafe_value(3,3).
deallocate.
execute(length_addendum,3).
retry_me_else(8).
call(integer,1,x(2)).
neck_cut.
put_constant(level(shallow),not_less_than_zero,x(1)).
put_structure(/,2,x(3)).
set_constant(length).
set_constant(2).
execute(domain_error,3).
trust_me(0).
put_constant(level(shallow),integer,x(1)).
put_structure(/,2,x(3)).
set_constant(length).
set_constant(2).
execute(type_error,3).
Is = [...].
?- inlined_instructions(19275, Is),maplist(portray_clause, Is).
get_value(x(1),3).
get_variable(x(3),1).
put_value(x(2),1).
execute(no_hat_call,1).
Is = [...].
?- inlined_instructions(19371, Is),maplist(portray_clause, Is).
allocate(2).
get_variable(y(1),2).
put_variable(y(2),2).
call(copy_term_nat,2).
put_structure(:,2,x(1)).
set_constant(lambda).
set_local_value(y(2)).
put_value(y(1),2).
deallocate.
execute(call,2).
Is = [...].
I see... the "existence_error", like: we: the Prolog system suddenly does not see the definition/predicate; as if the system is looking for the definition in the wrong context/module...
In some sense, your query ?- wam_instructions(test2/0,Instrutions). is all we need to know. Clearly, call/2 at the end is handled like an ordinary predicate. It just passes the term over but forgets that its first argument is a meta-predicate. So in this argument, a module qualification has to be passed further on. But there is none. And thus, in module lambda the meta-calls are resolved locally. Or that's my theory.
But then, (after consulting your original program):
?- test1.
true.
?- test2.
error(existence_error(procedure,length/2),length/2). % we are not happy with this
?- asserta((lambda:length(_,_):-throw(ha_gotit))).
true.
?- test2.
error(existence_error(procedure,length/2),length/2), unexpected.
throw(ha_gotit). % expected, but not found
?- lambda:length(1,2).
error(existence_error(procedure,length/2),length/2), unexpected.
?- asserta((l:length(_,_):-throw(ha_gotit))).
true.
?- l:length(1,2).
error(existence_error(procedure,l:length/2),length/2), unexpected.
So what is happening with these asserts??
This works as expected:
?- [user].
l:length(_,_) :- throw(ha_gotit).
?- l:length(A,B).
throw(ha_gotit).
?-
So it is only problem with assertions
Also after studying source code of loader.pl I can tell that correct modules are added to arguments of meta-predicates during (more-or-less) goal expansion. And code here is quite tricky and has a lot of special-cases, for example so called transitive goals which work afaik only for sequences of unifications using (=)/2, but don't work for implicit unifications (like unify(A, A)).
Maybe these aspects of the problem are obvious already to you all, but in case it helps ...
% Repro for failing lambda expressions
:- use_module(library(lists)).
:- use_module(library(clpz)).
:- use_module(library(error)).
:- use_module(library(lambda)).
:- use_module(library(debug)).
q_r(T/N, T:U) :- 0 #=< #T, 0 #=< #U, #N #= T + U.
%?- q_r(2/6, R).
%@ R = 2:4.
%?- maplist(\Q^T^U^(q_r(Q, T:U)), [1/3, 2/6], Ts, Us).
%@ error(existence_error(procedure,q_r/2),q_r/2).
% But with *explicit* qualification of user:q_r/2, ...
%?- maplist(\Q^T^U^(user:q_r(Q, T:U)), [1/3, 2/6], Ts, Us).
%@ Ts = [1,2], Us = [2,4].
% Unqualified q_r/2 also fine when used *inside* a predicate definition:
hmm(Qs, Ts, Us) :-
maplist(\Q^T^U^(q_r(Q, T:U)), Qs, Ts, Us).
%?- hmm([1/3, 2/6], Ts, Us).
%@ Ts = [1,2], Us = [2,4].
For reproduction it is helpful to minimize terms and dependencies on libraries and other code. In fact, even maplist/4 is not needed. Some things improved in rebis-dev 75e52068 compared to v0.9.4-201-gc39ea481. But not all of them.
The \ seems to remain a problem. Note that parameter passing works, or at least of the cases tested.
:- use_module(library(lists)).
:- use_module(library(lambda)).
q_r(2/6, 2:4).
hmm(Qs, Ts, Us) :-
maplist(\Q^T^U^q_r(Q, T:U), Qs, Ts, Us).
hmm2(Qs, Ts, Us) :-
call(maplist(\Q^T^U^q_r(Q, T:U), Qs, Ts, Us)).
hmm3(Qs, Ts, Us) :-
G_0 = maplist(\Q^T^U^q_r(Q, T:U), Qs, Ts, Us),
call(G_0).
hmm4(Qs, Ts, Us) :-
-G_0 = -maplist(\Q^T^U^q_r(Q, T:U), Qs, Ts, Us), % finally, teh bug
call(G_0).
hm2([Qx],[Tx],[Ux]) :-
call(\Q^T^U^q_r(Q, T:U), Qx, Tx, Ux).
hm4([Qx],[Tx],[Ux]) :-
-G_0 = - \Q^T^U^q_r(Q, T:U),
call(G_0, Qx, Tx, Ux).
hm :-
call(\ q_r(_,_) ).
end_of_file.
?- maplist(\Q^T^U^q_r(Q, T:U), [2/6], Ts, Us).
error(existence_error(procedure,q_r/2),q_r/2), unexpected.
Ts = [2], Us = [4]. % in rebis-dev
?- maplist(\Q^T^U^q_r(Q, T:U), [2/6], Ts, Us).
error(existence_error(procedure,q_r/2),q_r/2).
Ts = [2], Us = [4]. % in rebis-dev
?- hmm([2/6], Ts, Us).
Ts = [2], Us = [4].
?- hmm2([2/6], Ts, Us).
idem.
?- hmm3([2/6], Ts, Us).
idem.
?- hmm4([2/6],Ts,Us).
error(existence_error(procedure,q_r/2),q_r/2), unexpected. % same in rebis-dev
idem. % expected, but not found
?- call(\Q^T^U^q_r(Q, T:U), Qx, Tx, Ux).
error(existence_error(procedure,q_r/2),q_r/2), unexpected.
Qx = 2/6, Tx = 2, Ux = 4. % in rebis-dev
?- hm2([2/6],Ts,Us).
Ts = [2], Us = [4].
?- hm4([2/6],Ts,Us).
error(existence_error(procedure,q_r/2),q_r/2), unexpected. % same in rebis-dev
?- call(\Q^q_r(Q, _), Qx).
error(existence_error(procedure,q_r/2),q_r/2), unexpected.
Qx = 2/6. % in rebis-dev
?- call(Q^q_r(Q, _), Qx). % when called without `\` it works ...
Q = 2/6, Qx = 2/6.
?- call(\ q_r(_,_) ).
error(existence_error(procedure,q_r/2),q_r/2), unexpected.
true. % in rebis-dev
?- hm.
true.
@haijinSk: Excellent catch! I am very glad this works as expected with the most recent commit:
?- [Lambda] = [\N^length("",N)], call(Lambda,N).
Lambda = \0^length([],0), N = 0.
?- Lambda = \N^length("",N), Pred = Lambda, call(Pred,N).
Lambda = \0^length([],0), N = 0, Pred = \0^length([],0).
Yes!!! This is great!
Only as an aesthetic side note, with rustc 1.83.0 (90b35a623 2024-11-26), during compilation I saw this warning:
[...]
Compiling arcu v0.1.1
warning: unnecessary `unsafe` block
--> src/ffi.rs:92:9
|
92 | unsafe {
| ^^^^^^ unnecessary `unsafe` block
|
= note: `#[warn(unused_unsafe)]` on by default
[...]
I understand that the Rust compiler wants to be very helpful all the time and that does not mean that the reported thing has any consequences.
Thank you!!!