Question

I have a couple of predicates doing the same thing using lambda, tilde term from func, both lambda and func, and finally "pure Prolog" with neither lambda nor func:

:- use_module(library(lambda)).
:- use_module(library(func)).

both_lambda_and_func :-
    maplist(\X^(print(length(X,~))), [`one`,`two`,`three`]).

lambda_only :-
    maplist(\X^(length(X,Len),print(Len)), [`one`,`two`,`three`]).

func_only :-
    maplist(func_only_helper, [`one`,`two`,`three`]).
func_only_helper(X) :-
    print(length(X,~)).

normal_prolog :-
    maplist(normal_prolog_helper, [`one`,`two`,`three`]).
normal_prolog_helper(X) :-
    length(X,Len),
    print(Len).

All predicates should print 335 (lengths of strings in a list) and three of them do it correctly. The problem is that both_lambda_and_func/0 does not print anything and seems to go into infinite loop. I've tried to trace/0 the problem but it seems to be too complicated for me. Could you please tell me if I did something wrong or maybe this is some strange bug? I'm using SWI-Prolog 7.1.14, func 0.0.4, lambda 1.0.0.

Was it helpful?

Solution

?- listing(both_lambda_and_func).
both_lambda_and_func :-
    length(A, B),
    maplist(\A^print(B),
        [[111, 110, 101], [116, 119, 111], [116, 104, 114, 101, 101]]).

It's impossible to express the scope of the ~ term, that is rewritten blindly, in the wrong context. The program doesn't terminate because length/2 has both arguments free, then generate ever longer lists.

[trace] 4 ?- both_lambda_and_func.
   Call: (6) both_lambda_and_func
   Call: (7) length(_G1485, _G1486)
   Exit: (7) length([], 0)
^  Call: (7) apply:maplist(\[]^print(0), [[111, 110, 101], [116, 119, 111], [116, 104, 114, 101|...]])
   Call: (8) apply:maplist_([[111, 110, 101], [116, 119, 111], [116, 104, 114, 101|...]], user: \[]^print(0))
^  Call: (9) lambda: \([]^print(0), [111, 110, 101])
   Call: (10) copy_term_nat(user:[]^print(0), _G1541)
   Exit: (10) copy_term_nat(user:[]^print(0), user:[]^print(0))
^  Call: (10) lambda: ^([], print(0), [111, 110, 101])
^  Fail: (10) lambda: ^([], user:print(0), [111, 110, 101])
^  Fail: (9) lambda: \(user:[]^print(0), [111, 110, 101])
   Fail: (8) apply:maplist_([[111, 110, 101], [116, 119, 111], [116, 104, 114, 101|...]], user: \[]^print(0))
^  Fail: (7) apply:maplist(user: \[]^print(0), [[111, 110, 101], [116, 119, 111], [116, 104, 114, 101|...]])
   Redo: (7) length(_G1485, _G1486)
   Exit: (7) length([_G1478], 1)
^  Call: (7) apply:maplist(\[_G1478]^print(1), [[111, 110, 101], [116, 119, 111], [116, 104, 114, 101|...]])
   Call: (8) apply:maplist_([[111, 110, 101], [116, 119, 111], [116, 104, 114, 101|...]], user: \[_G1478]^print(1))
^  Call: (9) lambda: \([_G1478]^print(1), [111, 110, 101])
   Call: (10) copy_term_nat(user:[_G1478]^print(1), _G1547)
   Exit: (10) copy_term_nat(user:[_G1478]^print(1), user:[_G1546]^print(1))
^  Call: (10) lambda: ^([_G1546], print(1), [111, 110, 101])
^  Fail: (10) lambda: ^([_G1546], user:print(1), [111, 110, 101])
...

The call to ^ goes wrong

^  Fail: (10) lambda: ^([], user:print(0), [111, 110, 101])

because X it's already instantiated to [], while should be free...

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top