trealla icon indicating copy to clipboard operation
trealla copied to clipboard

library(clpb): Unexpected domain error

Open triska opened this issue 2 years ago • 3 comments

To reproduce this issue, please save the following example program as testing.pl:

:- use_module(library(clpb)).

permutation([], []).
permutation(List, [First|Perm]) :-
        select(First, List, Rest),
        permutation(Rest, Perm).

sat(_)  --> [].
sat(X*Y) --> [_], sat(X), sat(Y).
sat(X+Y) --> [_], sat(X), sat(Y).
sat(X#Y) --> [_], sat(X), sat(Y).
sat(card([0,1],[X,Y])) --> [_], sat(X), sat(Y).

vs_eqs(Vs, Eqs) :- phrase(vs_eqs(Vs), Eqs).

vs_eqs([]) --> [].
vs_eqs([V|Vs]) --> vs_eqs_(Vs, V), vs_eqs(Vs).

vs_eqs_([], _) --> [].
vs_eqs_([V|Vs], X) --> vs_eqs_(Vs, X), ( [X=V] ; [] ).

run(N) :-
        length(Ls, N),
        portray_clause(N),
        phrase(sat(Sat1), Ls),
        phrase(sat(Sat2), Ls),
        term_variables(Sat1-Sat2, Vs0),
        permutation(Vs0, Vs),
        vs_eqs(Vs, Eqs),
        findall(Vs, (sat(Sat1),sat(Sat2),maplist(call, Eqs),labeling(Vs)), Sols1),
        findall(Vs, (labeling(Vs),maplist(call,Eqs),sat(Sat1*Sat2)), Sols2),
        (   sort(Sols1, Sols), sort(Sols2, Sols) -> true
        ;   throw(neq-Sat1-Sat2-Eqs-Vs0-Vs-Sols1-Sols2)
        ),
        false.

run :- run(_).

And then do:

$ ./tpl -O0 testing.pl
Trealla Prolog (c) Infradig 2020-2023, v2.29.3
?- run.
0.
1.
   error(domain_error(clpb_variable,[_23,[_23,[_23|_24],_25],_25]),unknown([_23,[_23|_24],_25])-1), unexpected.

triska avatar Oct 08 '23 21:10 triska

Very nice, thank you a lot! Let's continue with #366.

triska avatar Oct 12 '23 19:10 triska

Was fixed due to a typo, so not really. Re-opening this.

infradig avatar Oct 13 '23 02:10 infradig

I now no longer get a domain error, so the specific instance of this issue seems resolved.

However, a different issue remains:

?- run.
0.
1.
   neq-_23*_24-(_25+_26)-[_23=_24,_25=_26]-[_23,_24,_25,_26]-[_23,_24,_25,_26]-[]-[[1,1,1,1]].

#369 may be a shorter example of this issue.

triska avatar Oct 13 '23 18:10 triska