Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

setof/3 ---> We are all doomed!!!

112 views
Skip to first unread message

Mostowski Collapse

unread,
Aug 11, 2022, 7:00:22 PM8/11/22
to
I had a discussion with Sloof Lirpa on Discord. He agrees
with Markus Triskas analysis of aggregate_all/3, an
analysis which can be transmutate to setof/3 from the

ISO core standard: So we would for example:

?- setof(X, member(X, [b,a,c]), [a]).
false.

But adding a constraint (X = a) would make the query succeed:

?- X=a, setof(X, member(X, [b,a,c]), [a]).
X = a.

This non-monotonic behaviour complicates reasoning
about programs considerably, and also makes declarative
debugging (library(debug)) inapplicable. Are there

monotonic alternatives that would be useful in at least
some of the cases in which this non-monotonic construct is
commonly used? It would be great to establish a more

declarative alternative.

Mostowski Collapse

unread,
Aug 11, 2022, 9:22:03 PM8/11/22
to

Same problem with negation as failure, credits go
to Elias Whitlow. So we would for example have:

?- \+ X = b.
false.
But adding a constraint (X = a) would make the query succeed:

?- X=a, \+ X = b.
X = a.

This non-monotonic behaviour complicates reasoning
about programs considerably, and also makes declarative
debugging (library(debug)) inapplicable. Are there

monotonic alternatives that would be useful in at least
some of the cases in which this non-monotonic construct is
commonly used? It would be great to establish a more

declarative alternative.

Mostowski Collapse

unread,
Aug 11, 2022, 9:24:48 PM8/11/22
to

Because of the problems, as long as there are no declarative
solutions around, maybe move these into a new Scryer
Prolog library(iso_impure)? At least the following ISO core

standard predicates would land there:

- (\+)/1
- (->)/2
- (\=)/2
- findall/3
- setof/3
- bagof/3

What else?

Mostowski Collapse

unread,
Aug 12, 2022, 2:24:39 AM8/12/22
to
Looks like its dooms day for most of ISO core standard and that the
language is completely wrecked. That (==)/2, ground/1 and nonvar/1
are also suspicious is seen here:

(==)/2 is non-monotonoic:
```
?- X == a.
false.

?- X = a, X == a.
X = a.
```
Further ground/1 is non-monotonoic:
```
?- ground(f(X)).
false.

?- X = a, ground(f(X)).
X = a.
```
Finally nonvar/1 is non-monotonic:
```
?- nonvar(X).
false.

?- X = a, nonvar(X).
X = a.
```

Mostowski Collapse

unread,
Aug 12, 2022, 2:39:54 AM8/12/22
to
Possibly sort/2 is also non-monotonic. Although the situation is
slightly different. In Scryer Prolog the predicate, when used in
a conjunction, can switch from false to error:

?- sort([1,2,3], X), X = [].
false.

?- X = a, sort([1,2,3], X), X = [].
error(type_error(list,a),sort/2).

So I guess Markus Triskas observation also applies to sort/2?
And possibly also to keysort/2?

Mostowski Collapse

unread,
Aug 12, 2022, 2:50:39 AM8/12/22
to
The is a real abyss in Prolog of non-monotonic predicates.
Same problem with length/2 from library(lists) in Scryer Prolog,
also non-monotonic:

?- use_module(library(lists)).
true.

?- length([1,2,3], X), X = a.
false.

?- X = a, length([1,2,3], X), X = a.
error(type_error(integer,a),length/2).

It would be maybe better if Prolog had no exceptions, and
would simply fail in such situations where it expects an integer,
and receives something else instead.

Mostowski Collapse

unread,
Aug 12, 2022, 2:56:58 AM8/12/22
to

For better declarativity, possibly some predicates need to be
made to fail, instead of throw an error, if they receive an
argument of the wrong type, like here:

?- length([1,2,3], a).
error(type_error(integer,a),length/2).

More declarative behaviour, based on Markus Triskas
observation, would be:

?- length([1,2,3], a).
false

Does Scryer Prolog already have a switch to switch off exceptions?
SWI-Prolog discourse had a long discussion errors considered
harmful dealing with this issue.

https://swi-prolog.discourse.group/t/errors-considered-harmful/3574/88

Mostowski Collapse

unread,
Aug 12, 2022, 3:53:33 AM8/12/22
to
> I had a discussion with Sloof Lirpa on Discord.

Anyway, who cares about non-monotonicity? Why would
one want to shoehorne declarativity into Prolog, when
it is a procedural and declarative language?

Just use a theorem prover if you want more extended
declarativity, covering more logical constructs than
those that Prolog offers.

Maybe this theorem prover is even written in Prolog!

Sloof Lirpa = April Fools

Have a nice Weekend everybody!

Mostowski Collapse

unread,
Aug 13, 2022, 6:03:08 PM8/13/22
to
Here is the Scryer Prolog challenge:

fCube: an efficient prover for Intuitionistic propositional Logic
https://rextester.com/SEOO25214

Can you make it run?

Mostowski Collapse

unread,
Aug 13, 2022, 6:16:11 PM8/13/22
to
The struggle is real, possibly a result of Fastfood McDonald
approach to Prolog? Dunno. Call the language BigMacLog then?

https://github.com/mthom/scryer-prolog/issues/1564

Mostowski Collapse

unread,
Aug 13, 2022, 6:23:30 PM8/13/22
to
For example subtract/3 has complexity

O(n*m)

And ord_subtract/3, if you do it wrong, and
insert sort/2 everywhere, has complexity:

O(n*log n + m*log m)

subtract/3 is better than ord_subtract/3 for m<<n.
But if you manage to elminate the sort/2,

then ord_subtract/2 is only O(n+m) and better again.
So there is a lot to deliberate.

Mostowski Collapse

unread,
Aug 13, 2022, 7:09:34 PM8/13/22
to
Why Aprils Fool? Well this here was 10 Apr 2021, almost Aprils Fool day:

How it started:

Scryer Prolog sets a new standard for efficient encoding of lists of
characters, which we mean when we say "strings" in the context of
Scryer Prolog. A key advantage of the efficient encoding is that

DCGs can be used for describing the string, since it is simply a list.
A good infrastructure for processing JSON with Scryer Prolog uses
this representation, and describes JSON format with a DCG.
https://github.com/mthom/scryer-prolog/discussions/892

How its going:

$ target/release/scryer-prolog -v
"v0.9.0-181-g8e9302ea"
$ target/release/scryer-prolog
?- time((between(1,1000,_), data(X), json_chars(Y,X,[]), fail; true)).
% CPU time: 1.953s
true.

/* SWI-Prolog (threaded, 64 bits, version 8.5.14) */
?- time((between(1,1000,_), data(X), atom_json_term(X,Y,[]), fail; true)).
% 48,000 inferences, 0.000 CPU in 0.007 seconds (0% CPU, Infinite Lips)
true.

The test data was simply:

data("{ \"a\":123 }").

I got the idea for this nasty test data, after inspecting the source code
of the new library(serialization/json). Just compare to what Jan W. is doing.

Mostowski Collapse

unread,
Aug 13, 2022, 7:18:08 PM8/13/22
to

New JSON parser is extremly slow
https://github.com/mthom/scryer-prolog/issues/1566

Mostowski Collapse

unread,
Aug 13, 2022, 7:45:08 PM8/13/22
to
Here some penny of thought. If Scryer Prolog would:

1. Rethink the notion of pure, and incorporate some
results of logic programming concerning SLDNF

2. Allow (+)//1 in DCG, which was refused here
on dubious grounds:

https://github.com/mthom/scryer-prolog/issues/1479

Then it could abandon the old fashioned DCG, were D is taken
literally as definite, i.e. without negation and pure. And it could
move towards the more modern grammar formalism:

parsing expression grammar (PEG)
https://en.wikipedia.org/wiki/Parsing_expression_grammar

Its quite easy to map PEG to DCG, where D is not interpreted
that strict. And this can give much more efficient parsers, that
are at the same time concise and declarative.

Edit 14.08.2022
Even the Ruby ISO standard uses some PEG inspired formalism
for their grammar. Check it out.

Mostowski Collapse

unread,
Aug 13, 2022, 7:54:56 PM8/13/22
to
But with (\+)//1 you might have still spurious choice points,
which slows down a Prolog system. The ultimate fun begins when
you use cut (!)/0 and know its a kind of (\+)//1.

But you could also try to refactor the JSON DCG, find more
common prefixes in the parser, and try something definite, i.e.
pure and without negation. But you then possibly wont get

rid of spurious choice points. Maybe if you do some tricks
with multiple argument indexing, if the indexing also catches
the DCG input? Not sure, maybe?

Mostowski Collapse

unread,
Aug 14, 2022, 4:20:33 AM8/14/22
to
Ciao Prolog is also some night mare, using the new playground:

?- use_module(library(lists)).
Note: module lists already in executable, just made visible

?- subtract([c,a,b],[a],X).
{ERROR: No handle found for thrown exception
error(existence_error(procedure,'user:subtract'/3),'user:subtract'/3)}

Mostowski Collapse

unread,
Aug 15, 2022, 5:44:26 AM8/15/22
to
And the winner is:

In the category "muito loco":
- Ciao Prolog: A lot of new tickets and a lot of bla bla

In the category "gets work done":
- SWI-Prolog: Just copy paste the rextester Prolog text to here, it wurks!
https://dev.swi-prolog.org/wasm/shell

Mostowski Collapse schrieb am Sonntag, 14. August 2022 um 00:03:08 UTC+2:

Mostowski Collapse

unread,
Aug 15, 2022, 7:17:39 PM8/15/22
to
Pay attention! So Logtalk and Scryer struggles with ‘|’?
https://github.com/mthom/scryer-prolog/issues/1571

Its not an issue for the fCube version I posted here. Since it has:

:- op(700, xfy, <=>).
:- op(600, xfy, =>).
:- op(500, xfy, v).
:- op(400, xfy, &).
:- op(300, fy, ~).

fCube: an efficient prover for Intuitionistic propositional Logic
in Rextester - Joseph Vidal-Rosset, 2022
https://rextester.com/SEOO25214

Rextester is funny, it has an integrated version management system,
maybe a wikipedia variant? Will Ciao or SWIPL WASM have the same?

Mostowski Collapse

unread,
Aug 15, 2022, 7:21:19 PM8/15/22
to
Oops its the other way around, the Joseph Vidal-Rosset
version is the dangerous version it has:

% operator definitions (TPTP syntax)
:- op( 500, fy, ~). % negation
:- op(1000, xfy, &). % conjunction
:- op(1100, xfy, '|'). % disjunction
:- op(1110, xfy, =>). % conditional
:- op(1120, xfy, <=>). % biconditional

Well I started allowing '|' redefinition in Jekejeke Prolog and
Dogelog Player, SWI-Prolog allows the same, no error here:

/* SWI-Prolog (threaded, 64 bits, version 8.5.14) */
?- op(1100, xfy, '|').
true.

This was done in favor of all the legacy TPTP syntax stuff.

Mostowski Collapse

unread,
Aug 15, 2022, 7:23:47 PM8/15/22
to
Ciao Prolog can do the same, I get in the current Ciao Prolog Playground:

?- current_op(X,Y,'|').
X = 1105,
Y = xfy ?
yes

?- op(1100, xfy, '|').
yes

?- current_op(X,Y,'|').
X = 1100,
Y = xfy ?
yes

Mostowski Collapse

unread,
Aug 15, 2022, 8:19:36 PM8/15/22
to
I still don't understand why '|' even landed in DCG,
it only causes problems. Back in the 1980's nobody

used DCG like that:

The first clause on the right-hand side:
verb (change) — >
[c] ; [ch] ; [change] ; [set] .
is satisfied if the token is any one of the four listed
(the ";" is Prolog's way of ex- pressing the OR relation among clauses).
https://archive.org/details/byte-magazine-1987-08/page/n181/mode/2up

And still your own folks nowadays dont use '|':
```
json_ws -->
( parsing ->
json_ws_greedy
; json_ws_lazy
).
```
https://github.com/mthom/scryer-prolog/blob/master/src/lib/serialization/json.pl

Mostowski Collapse

unread,
Aug 15, 2022, 8:40:57 PM8/15/22
to
I like the quality of the new JSON parser for Scryer Prolog.
Did anybody review the code?

I get for example:

?- number_chars(X, "7.075657757024522e-7").
X = 7.075657757024522e-7.
?- json_chars(X, "7.075657757024522e-7", "").
X = number(7.075657757024521e-7)

The two results are different:

?- C = "7.075657757024522e-7",
number_chars(X, C),
json_chars(number(Y), C, ""),
X == Y.
false.

LoL

Mostowski Collapse

unread,
Aug 15, 2022, 8:47:12 PM8/15/22
to
SWI-Prolog doesn't have this error:

?- use_module(library(http/json)).
true.

?- number_chars(X, "7.075657757024522e-7").
X = 7.075657757024522e-7.

?- atom_json_term('7.075657757024522e-7', X, []).
X = 7.075657757024522e-7.

Mostowski Collapse

unread,
Aug 15, 2022, 8:50:28 PM8/15/22
to
BTW: I used this fuzzer to find the number:

?- repeat, random(X), Y is X/1000000,
number_chars(Y,C),
json_chars(number(Z),C,""), Z \== Y.

See also:
https://en.wikipedia.org/wiki/Fuzzing

Mostowski Collapse

unread,
Aug 15, 2022, 9:12:23 PM8/15/22
to
This is also extremly cringe:

$ cd scryer-prolog
$ target/release/scryer-prolog
?- use_module(library(serialization/json)).
true.
?- json_chars(X, "{}", "").
X = pairs([])
; ... .
?- json_chars(pairs([]), X, "").
X = "{}"
; X = "{} "
; X = "{} "
; X = "{} "
; X = "{} "
; X = "{} "
; X = "{} "
; X = "{} "
; X = "{} "
; X = "{} "
; X = "{} "

Who wants such a nonsense?

Mostowski Collapse

unread,
Aug 18, 2022, 1:44:45 PM8/18/22
to
C-Prolog had this:

/* File : pl/grammar
Author : Fernando Pereira
Updated: Wednesday February 1st, 1984, 8:38:15 pm
Purpose: translation of grammar rules
*/

$t_body(!, S, S, !) :- !.
$t_body([], S, S1, S=S1) :- !.
$t_body([X], S, SR, 'C'(S,X,SR)) :- !.
$t_body([X|R], S, SR, ('C'(S,X,SR1),RB)) :- !,
$t_body(R, SR1, SR, RB).
$t_body({T}, S, S, T) :- !.
$t_body((T,R), S, SR, (Tt,Rt)) :- !,
$t_body(T, S, SR1, Tt),
$t_body(R, SR1, SR, Rt).
$t_body((T;R), S, SR, (Tt;Rt)) :- !,
$t_body(T, S, S1, T1), $t_fill(S, SR, S1, T1, Tt),
$t_body(R, S, S2, R1), $t_fill(S, SR, S2, R1, Rt).
$t_body(T, S, SR, Tt) :-
$extend([S,SR], T, Tt).

No (''|')/2. But also no (->)/2 and no (\+)/1.

LoL

Mostowski Collapse

unread,
Aug 30, 2022, 9:02:43 PM8/30/22
to
Intersting bug in Scryer Prolog, only one solution:

$ ../target/release/scryer-prolog -v
"v0.9.0-175-g6b8e6204"
$ ../target/release/scryer-prolog
?- [tictac].
true.
?- best(["x-o", "o-x", "-x-"],x,Y).
Y = ["x-o","o-x","-xx"].

But then SWI-Prolog gives me 4 solutions:

/* SWI-Prolog (threaded, 64 bits, version 8.5.14) */
?- set_prolog_flag(double_quotes, chars).
true.

?- best(["x-o", "o-x", "-x-"],x,Y).
Y = [[x, x, o], [o, -, x], [-, x, -]] ;
Y = [[x, -, o], [o, x, x], [-, x, -]] ;
Y = [[x, -, o], [o, -, x], [x, x, -]] ;
Y = [[x, -, o], [o, -, x], [-, x, x]].

Test case is here in this tar ball:

http://www.rubycap.ch/gist/bench.tar.gz

Mostowski Collapse

unread,
Aug 30, 2022, 9:09:56 PM8/30/22
to
And Trealla has also no problem:

$ ../tpl -v
Trealla Prolog (c) Infradig 2020-2022, v2.1.11
$ ../tpl
?- ['tictac.p'].
true.
?- best(["x-o", "o-x", "-x-"],x,Y).
Y = ["xxo","o-x","-x-"]
; Y = ["x-o","oxx","-x-"]
; Y = ["x-o","o-x","xx-"]
; Y = ["x-o","o-x","-xx"].

Mostowski Collapse

unread,
Aug 30, 2022, 9:19:10 PM8/30/22
to
Saw the bug first in an extremly fast tictac runtime,
and then used this fuzzer to find such a test case:

random_board([[A,B,C],[D,E,F],[H,I,J]]) :-
random_member(A, [o,-,x]),
random_member(B, [o,-,x]),
random_member(C, [o,-,x]),
random_member(D, [o,-,x]),
random_member(E, [o,-,x]),
random_member(F, [o,-,x]),
random_member(H, [o,-,x]),
random_member(I, [o,-,x]),
random_member(J, [o,-,x]).

Fuzzers are lit!

Mostowski Collapse

unread,
Aug 31, 2022, 5:35:34 AM8/31/22
to
Nice, Ciao Prolog can be built from GitHub.
Its blazing fast, and doesn't abort:

Test Ciao ECLiPSe
nrev 41 32
crypt 81 62
deriv 94 94
poly 66 62
qsort 79 78
tictac 174 110
queens 80 78
query 231 187
mtak 75 94
perfect 169 485
calc 82 78
Total 1’172 1’360

Was testing against ECliPSe 61 and on WSL 2.
Can ECLiPSe also be built from GitHub?

Mostowski Collapse

unread,
Sep 6, 2022, 6:49:32 PM9/6/22
to
Sloof Lirpa has changed his mind. He now says we don't
need library(sets) or library(ordsets), we can for example
do set union where naturally with:

?- A = [1,2,3], B=[2,3,4], setof(X, (member(X,A); member(X,B)), L).
A = [1, 2, 3],
B = [2, 3, 4],
L = [1, 2, 3, 4].

Sloof Lirpa now even makes the claim that setof/3 is
quite declarative. He gives this example, students that
have some courses:

course(berta, english).
course(berta, math).
course(berta, french).

course(carlo, math).
course(carlo, french).
course(carlo, biology).

He gives now this example of monotonicity:

?- setof(X, (course(berta, X), course(carlo, X)), L).
L = [french, math].

?- setof(X, (course(A, X), course(B, X)), L), A=berta, B=carlo.
A = berta,
B = carlo,
L = [french, math] ;
false.

Mostowski Collapse schrieb am Freitag, 12. August 2022 um 01:00:22 UTC+2:
> I had a discussion with Sloof Lirpa on Discord. He agrees
> with Markus Triskas analysis of aggregate_all/3, an
> analysis which can be transmutate to setof/3 from the
>
> ISO core standard: So we would for example:
>
> ?- setof(X, member(X, [b,a,c]), [a]).
> false.
>
> But adding a constraint (X = a) would make the query succeed:
>
> ?- X=a, setof(X, member(X, [b,a,c]), [a]).
> X = a.
>
> This non-monotonic behaviour complicates reasoning
> about programs considerably, and also makes declarative
> debugging (library(debug)) inapplicable. Are there
>
> monotonic alternatives that would be useful in at least
> some of the cases in which this non-monotonic construct is
> commonly used? It would be great to establish a more
>
> declarative alternative.

Mostowski Collapse

unread,
Sep 6, 2022, 6:54:00 PM9/6/22
to
We could argue Sloof Lirpa change of mind was based
on a lucky coincidence. Conjunction and setof/3 worked
indeed quite declaratively. But what about Disjunction

and setof/3, can we do the same?

?- setof(X, (course(berta, X); course(carlo, X)), L).
L = [biology, english, french, math].

?- setof(X, (course(A, X); course(B, X)), L), A=berta, B=carlo.
A = berta,
B = carlo,
L = [biology, french, math] ;
A = berta,
B = carlo,
L = [english, french, math] ;
false.

Seems not to be monotonic anymore. Can we
define a new setof/3, that would be still monotonic
also for disjunction? Whats the problem in the above

exactly, any ideas?
0 new messages