ichiban / prolog

The only reasonable scripting engine for Go.
MIT License
564 stars 27 forks source link

writeq/1 sometimes inserts ... #297

Closed UWN closed 1 year ago

UWN commented 1 year ago

writeq/1 sometimes inserts ... instead of the expected terms. This seems to happen at random and not at a particular depth. Many implementations provide the additional write_option max_depth/1 via 5.5.12, such that those ... will be inserted at a certain level. But this must not happen in writeq/1. Nevertheless it happens as follows.

:- initialization(ti).

ti :-
   length(Es, 3),
   Post = [_|_],
   phrase((seq(Pre),[true],seq(Post)),Es),
   phrase((seq(Post),seq(Pre),[true]),EsR),
   maplist(skel,Pre),
   maplist(skel,Post),
   writeq(Es),nl,
   false.
ti.

seq([]) --> [].
seq([E|Es]) --> [E], seq(Es).

skel(k(X)) :- skel2(X).

skel2("a").
skel2("b").

And now if this is consulted, I get:

?- [ediftcrvichidb].                       
[true,k([a]),k(...)]
[true,k([a]),k([b])]
[true,k([b]),k([a])]
[true,k([b]),k(...)]
[k([a]),true,k(...)]
[k([a]),true,k([b])]
[k([b]),true,k([a])]
[k([b]),true,k(...)]
true.

These occurrences of ... seem to be completely random.

UWN commented 1 year ago

Much smaller example:

?- writeq("a"+"a"),nl.
[a]+...    % unexpected
true.
ichiban commented 1 year ago

This was a bug in the code where I tried to truncate already visited compounds (e.g. L = [a, b|L]).

I'm preparing a fix #298.

$ $(go env GOPATH)/bin/1pl
Top level for ichiban/prolog (devel)
This is for testing purposes only!
See https://github.com/ichiban/prolog for more details.
Type Ctrl-C or 'halt.' to exit.
?- [ediftcrvichidb].
[true,k([a]),k([a])]
[true,k([a]),k([b])]
[true,k([b]),k([a])]
[true,k([b]),k([b])]
[k([a]),true,k([a])]
[k([a]),true,k([b])]
[k([b]),true,k([a])]
[k([b]),true,k([b])]
true.
?- writeq("a"+"a"),nl.
[a]+[a]
true.
?- L = [a, b|L], writeq(L), nl.
[a,b,a|...]
L = [a,b,a|...].
?- 
UWN commented 1 year ago

Just to be sure, please note that the text written should in any case be valid Prolog text. So if you insert ... with option max_depth/1 then you need to add spaces, too. This is Scryer:

p(1).
p(E+1):-p(E).

?- p(E).
   E = 1
;  E = 1+1
;  E = 1+1+1
;  E = 1+1+1+1
;  E = 1+1+1+1+1
;  E = 1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = 1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = ... + ... +1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  E = ... + ... +1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1+1
;  ... .

So there is a space between ... and + since otherwise they would parse as one token.

ichiban commented 1 year ago

Thank you for the heads-up! I fixed the code so that it writes ... as an atom.

$ $(go env GOPATH)/bin/1pl
Top level for ichiban/prolog (devel)
This is for testing purposes only!
See https://github.com/ichiban/prolog for more details.
Type Ctrl-C or 'halt.' to exit.
?- C = C+C, writeq(C), nl.
... + ...
C = ... + ....
?- 

Also, I implemented max_depth/1.

$ $(go env GOPATH)/bin/1pl
Top level for ichiban/prolog (devel)
This is for testing purposes only!
See https://github.com/ichiban/prolog for more details.
Type Ctrl-C or 'halt.' to exit.
?- assertz(p(1)).
true.
?- assertz((p(E+1):-p(E))).
E = _62.
?- p(E), write_term(E, [max_depth(3)]), nl.
1
E = 1;
1+1
E = 1+1;
1+1+1
E = 1+1+1;
... + ... +1+1
E = 1+1+1+1;
... + ... +1+1
E = 1+1+1+1+1.
?- 
|- 
UWN commented 1 year ago

(just to be sure, this is still not fixed in main, right?)

ichiban commented 1 year ago

Sorry for being late. It's in v1.1.1 but there's a new bug in 1pl so I'm going to release v1.1.2 soon.

ichiban commented 1 year ago

Now it's fixed in main and released as v1.1.2.

$ go install github.com/ichiban/prolog/cmd/1pl@latest
go: downloading github.com/ichiban/prolog v1.1.2
$ $(go env GOPATH)/bin/1pl
Top level for ichiban/prolog v1.1.2
This is for testing purposes only!
See https://github.com/ichiban/prolog for more details.
Type Ctrl-C or 'halt.' to exit.
?- [ediftcrvichidb]. 
[true,k([a]),k([a])]
[true,k([a]),k([b])]
[true,k([b]),k([a])]
[true,k([b]),k([b])]
[k([a]),true,k([a])]
[k([a]),true,k([b])]
[k([b]),true,k([a])]
[k([b]),true,k([b])]
true.
?- writeq("a"+"a"),nl.
[a]+[a]
true.
?- L = [a, b|L], writeq(L), nl.
[a,b,a|...]
L = [a,b,a|...].
?- C = C+C, writeq(C), nl.
... + ...
C = ... + ....
?- assertz(p(1)).
true.
?- assertz((p(E+1):-p(E))).
E = _490.
?- p(E), write_term(E, [max_depth(3)]), nl.
1
E = 1;
1+1
E = 1+1;
1+1+1
E = 1+1+1;
... + ... +1+1
E = 1+1+1+1;
... + ... +1+1
E = 1+1+1+1+1.
?- 
UWN commented 1 year ago

Good. Closing. Note however, that your particular treatment of infinite lists is unusual.

?- L = [a, b|L], write_term(L,[max_depth(9)]),nl,false.
[a,b,a|...]
false.

Other* implementations show 8 or 9 elements.

Now, from a standard's viewpoint this case is STO, and thus undefined. So you are free to do whatever you like. But I just wanted to note this, since you are effectively introducing some non-determinism into your implementation. Think of

?- L=[_,_,_,_|_], L=[a,b|L], write_term(L,[max_depth(9)]), nl, fail.
[a,b,a,b,a|...]
false.
?- L=[a,b|L], L=[_,_,_,_|_], write_term(L,[max_depth(9)]), nl, fail.
[a,b,a|...]
false.

*) Scryer is similar to Ichiban. Tau is entirely different as it does not create infinite terms at all. But SICStus, GNU, XSB, ECLiPSe all behave the same.

ichiban commented 1 year ago

I changed the behavior of write_term/[2, 3] a bit. If max_depth(_) is present, it doesn't truncate for cyclic lists. Now those 2 queries work the same way.

$ $(go env GOPATH)/bin/1pl
Top level for ichiban/prolog v1.1.3
This is for testing purposes only!
See https://github.com/ichiban/prolog for more details.
Type Ctrl-C or 'halt.' to exit.
?- L=[_,_,_,_|_], L=[a,b|L], write_term(L,[max_depth(9)]), nl, fail.
[a,b,a,b,a,b,a,b,a|...]
false.
?- L=[a,b|L], L=[_,_,_,_|_], write_term(L,[max_depth(9)]), nl, fail.
[a,b,a,b,a,b,a,b,a|...]
false.