ciao-lang / ciao

Ciao is a modern Prolog implementation that builds up from a logic-based simple kernel designed to be portable, extensible, and modular.
https://ciao-lang.org
GNU Lesser General Public License v3.0
268 stars 20 forks source link

revisit lists.pl (was (playground) Feature request subtract/3, list_to_set/2, etc..) #60

Closed Jean-Luc-Picard-2021 closed 2 years ago

Jean-Luc-Picard-2021 commented 2 years ago

Trying to port fCube:

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

The porting turns out as a little night mare. I get in the new Ciao playground:

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

yes
?- union([1,3],[2,3],X).

X = [1,2,3] ? 

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

For subtract, if you are not playing with variables, you can import subtract/3 from library(idlists). It is also easy enough to write it directly of course. But it would indeed be a good idea to have a subtract definition in lists, unless someone (Jose?) sees a problem, will do. As for the port, note that subtract is not part of the standard, and different Prologs have ended up having things in different places. But it is great to move towards convergence as much as possible, of course!

Jean-Luc-Picard-2021 commented 2 years ago

Ok, interesting.

jfmc commented 2 years ago

Our idlists module was written by Francisco Bueno, including useful predicates which were not in our original lists module (years before I started working in the CLIP Lab so probably Manuel knows better). I had a look it we would have no problem with merging idlists into lists (those predicates seem standard in other Prologs nowadays).

As SWI mentions in their documentation: "Virtually every Prolog system has library(lists), but the set of provided predicates is diverse. There is a fair agreement on the semantics of most of these predicates, although error handling may vary."

For reference:

Some of systems above include meta predicates like maplist/N in the lists.pl module. Ciao avoids doing it.

Jean-Luc-Picard-2021 commented 2 years ago

It seems to have has a different semantics than what landed in SWI-Prolog library(lists), since the spec of the module says:

The operations in this module handle lists by performing equality checks via identity instead of unification. https://ciao-lang.org/ciao/build/doc/ciao.html/idlists.html

But there are other proposals around for a proper idlists module, like here:

Prolog Subtract List Unification

var_memberchk(A0, [A1|_]) :- 
    A0 == A1, !.
var_memberchk(A0, [_|R]) :- 
    var_memberchk(A0, R).

https://stackoverflow.com/a/9490332/17524790

Or here, using the eq_ prefix similar to the ord_ prefix:

This module provides unordered sets. http://pages.xlog.ch/srctab/doclet/docs/05_run/common/jekpro/frequent/experiment/sets.html

Jean-Luc-Picard-2021 commented 2 years ago

Why is there a semantic difference. You can try yourself,

in Ciao Playground:

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

?- subtract([C,A,B],[A],X).
X = [C,B] ?

And in SWI-Prolog:

?- subtract([C,A,B],[A],X).
C = A, A = B,
X = [].

So Ciao Prolog code implicitly using the eq_subtract/3 semantics by using subtract/3, wouldn't be portable into SWI-Prolog using its subtract/3 there.

Since the Ciao Prolog code might exactly use/need the identity feature. This overloading/clash leads to error prone and hard to debug code.

pmoura commented 2 years ago

Trying to port fCube:

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

The porting turns out as a little night mare.

https://github.com/LogtalkDotOrg/logtalk3/tree/master/ports/fcube

$ logtalk_tester -p ciao -s ~/Documents/Logtalk/
% Batch testing started @ 2022-08-14 20:56:50
%         Logtalk version: 3.58.0-b01
%         Ciao Prolog version: 1.21.0
%
% logtalk3/ports/fcube
%         12 tests: 0 skipped, 12 passed, 0 failed (0 flaky)
%         completed tests from object tests in 12 seconds
%         clause coverage 56.59574468085106%
%
% 1 test sets: 1 completed, 0 skipped, 0 broken, 0 timedout, 0 crashed
% 12 tests: 0 skipped, 12 passed, 0 failed (0 flaky)
%
% Batch testing ended @ 2022-08-14 20:57:03

P.S. The port is, of course, not Ciao specific. But it does expose parsing bugs in Scryer Prolog and Trealla Prolog.

mherme commented 2 years ago

It seems to have has a different semantics than what landed in SWI-Prolog library(lists), since the spec of the module says:

The operations in this module handle lists by performing equality checks via identity instead of unification. https://ciao-lang.org/ciao/build/doc/ciao.html/idlists.html

Note that these differences are on purpose (special handling of variables keeping them distinct instead un unifying them) and are explained in the documentation:

https://ciao-lang.org/ciao/build/doc/ciao.html/idlists.html

(or by the code, which is quite clear -- note that essentially all the Ciao libraries are written in Prolog).

But there are other proposals around for a proper idlists module, like here:

Prolog Subtract List Unification

var_memberchk(A0, [A1|_]) :- 
    A0 == A1, !.
var_memberchk(A0, [_|R]) :- 
    var_memberchk(A0, R).

https://stackoverflow.com/a/9490332/17524790

Or here, using the eq_ prefix similar to the ord_ prefix:

This module provides unordered sets. http://pages.xlog.ch/srctab/doclet/docs/05_run/common/jekpro/frequent/experiment/sets.html

Note that this seems the exact same definition as the subtract/3 in Ciao’s idlists library module (except the names of the variables are ABC here instead of the meaningful names in Ciao's library). This module is at least 22 years old, probably more (I did not have time to check back before 2000).

In any case, as mentioned by @jmfc adding a standard/non-id subtract/3 is no problem: we can do it instantly. There is no risk of confusion since the different subtracts are in different modules.

Jean-Luc-Picard-2021 commented 2 years ago

list_to_set/2 is also missing in Ciao Prolog Playground library(lists):

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

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

The SWI-Prolog code of this predicate is extremly complex, I guess there is a simpler solution based on memberchk/2. And that predicate that would use identity, should ideally have

a different name. Although SWI-Prolog doesn't do it like that.

jfmc commented 2 years ago

I suppose that SWI code for list_to_set/2 may be complex to ensure N*log(N) complexity.

Jean-Luc-Picard-2021 commented 2 years ago

Could be a long term goal, to have such complexity, had in mmy mind, by refering to a simpler solution based on memberchk/2, something simpler and also more

expensive complexity wise. Don't know whether fCube will not anymore run, when a simpler solution is used.

jfmc commented 2 years ago

This should have a good complexity (I had not time yet to check if the semantics are OK).

:- use_module(library(assoc)).

list_to_set(Xs, Ys) :-
    empty_assoc(Seen),
    list_to_set_(Xs, Seen, Ys).

list_to_set_([], _Seen, []).
list_to_set_([X|Xs], Seen, Ys) :-
    ( put_assoc(X, Seen, t, Seen2, no) -> Ys = [X|Ys2]
    ; Seen = Seen2, Ys = Ys2
    ),
    list_to_set_(Xs, Seen2, Ys2).

Scryer solution (probably also SWI) is based on sorting all elements and then picking the first occurrences.

Jean-Luc-Picard-2021 commented 2 years ago

The SWI Prolog spec requires input order, no sorting allowed. Maybe SWI Prolog has somewhere burried some test cases as well?

True when Set has the same elements as List in the same order. The left-most copy of duplicate elements is retained. https://www.swi-prolog.org/pldoc/doc_for?object=list_to_set/2

Its not only in spec, its also the behaviour:

/* SWI-Prolog (threaded, 64 bits, version 8.5.14) */
?- list_to_set([c,a,b,a], X).
X = [c, a, b].

So not sure whether Scryer Prolog does the right thing? On the other hand your implementation is possibly correct?

Edit 15.08.2022 Interestingly Scryer Prolog has list_to_set/2 already for long, and the chars display gives a different display of the same test case:

$ target/release/scryer-prolog
?- use_module(library(lists)).
   true.
?- list_to_set([c,a,b,a], X).
   X = "cab".
jfmc commented 2 years ago

SICStus also implements list_to_set/2 (in the sets.pl module) https://sicstus.sics.se/sicstus/docs/4.6.0/html/sicstus/lib_002dsets.html#index-list_005fto_005fset_002f2-_0028sets_0029-1

It is funny that SICStus does not recommend using sets.pl but ordsets.pl ("Please note: You should probably not use this module. The ordered representation used in library(ordsets) is much more efficient, but these routines were designed before sort/2 entered the language.")

Jean-Luc-Picard-2021 commented 2 years ago

Here is some empirical data, from SWI-Prolog, the tradeoff between sets and ordsets:

single element insert via union/3 is faster than via ord_union/3.

(No C code involved, was using union4/3)

?- findall(X,(between(1,10000,_),random(1,10000,X)),L), 
     time((between(1,10000,_),
     random(1,10000,Y), union4([Y],L,_), fail; true)).
% 63,128,346 inferences, 3.250 CPU in 3.287 seconds (99% CPU, 19424106 Lips)

?- findall(X,(between(1,10000,_),random(1,10000,X)),L), sort(L,R), 
     time((between(1,10000,_),
     random(1,10000,Y), ord_union([Y],R,_), fail; true)).
% 96,026,708 inferences, 5.516 CPU in 5.564 seconds (99% CPU, 17409941 Lips)

The library ordset pays off when you insert like 5 elements in a batch:

?- findall(X,(between(1,10000,_),random(1,10000,X)),L),
    time((between(1,10000,_),
    findall(Y,(between(1,5,_), random(1,10000,Y)), H), 
         union4(H,L,_), fail; true)).
% 315,183,160 inferences, 15.984 CPU in 15.991 seconds (100% CPU, 19718204 Lips)

?- findall(X,(between(1,10000,_),random(1,10000,X)),L),sort(L,R),
    time((between(1,10000,_),
    findall(Y,(between(1,5,_), random(1,10000,Y)), H),sort(H,J),
        ord_union(J,R,_), fail; true)).
% 157,835,640 inferences, 7.812 CPU in 7.814 seconds (100% CPU, 20202962 Lips)
Jean-Luc-Picard-2021 commented 2 years ago

What about this one, i.e. memberchk/2. Sorry for not providing a complete list of requirements. But this was a little surprise that it is missing:

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

?- memberchk(a,[b,a,c]).
{ERROR: No handle found for thrown exception 
error(existence_error(procedure,'user:memberchk'/2),'user:memberchk'/2)}
aborted
mherme commented 2 years ago

There is a memberchck/2 in idlists (this is the one with ==/2), or you can just add the two lines:

memberchk(Element, [Element|_]) :- !.
memberchk(Element, [_N|Rest]) :-
    memberchk(Element, Rest).

May indeed be a good idea to add it in lists.pl of course.

Jean-Luc-Picard-2021 commented 2 years ago

With Novacore and Liblets its not needed anymore. Can load ciao/lists.pl or swi/lists.pl depending on application.

jfmc commented 2 years ago

This is issue is still relevant and useful for us (it describes differences in the exported predicates from lists.pl). I'll keep it open and rename the title.

jfmc commented 2 years ago

Thanks. Yes, all those provers by Jens Otten work in Ciao with almost no changes.

Most portable Prolog (in the sense of running in several systems) ends up implementing their own 'stdlib.pl' module with some machinery to support one or other Prolog. Conditional compilation is a good way to do it (it has was available in many systems at least since the Prolog Commons initiative).

lists.pl is just the tip of the iceberg. Probably @pmoura is the right person to ask. Until Prolog systems adopt better mechanisms to synchronize or reuse their (standard) libraries, for some applications LogTalk may be a solution if you care about "extreme" portability.

Jean-Luc-Picard-2021 commented 2 years ago

Please note its only Logtalk, and not LogTalk. Does Logtalk run in the browser? Can you combine it with Ciao Prolog playground?

It has an old fashioned file to file pipeline, I have not yet seen it in some playground. Can you make it run in Ciao Prolog playground?

(Please note: This was originally a (playground) question)

jfmc commented 2 years ago

Note that the playground is not a separate Ciao implementation. It is just a "Ciao distribution" (a selection of modules) that runs on the browser.

Jean-Luc-Picard-2021 commented 2 years ago

What do you mean by "just"? Do you say I can run .lgt files in the Ciao Prolog playground? I have clarified my question here:

(playground) Can I run Logtalk from within the new Ciao Prolog Playground? https://\github.com/ciao-lang/ciao/issues/64

Jean-Luc-Picard-2021 commented 2 years ago

@jfmc wrote:

For reference:

I am still looking for the ultimate authorative references from the past. I find, with the comment:

%   File   : LISTUT.PL
%   Author : Bob Welham, Lawrence Byrd, and R.A.O'Keefe
%   Converted to NIP: K Johnson, 11.8.87
%   Updated: 12 February 1985
%   Purpose: list processing utilities

%   This module requires
%   listtoset/2 (from SetUtl.Pl) for remove_dups/2

https://www.j-paine.org/prolog/tools/files/listut.pl

So lets see whether there is a setutl.pl as well, and there you find:

%   File   : SETUTL.PL
%   Author : Lawrence Byrd + R.A.O'Keefe
%   Updated: 19 July 1984
%   Purpose: Set manipulation utilities

%   subtract/3,     %  Set x Set -> Set
%   listtoset/2,        %  List -> Set

https://www.j-paine.org/prolog/tools/files/setutl.pl

Hope this helps!

Jean-Luc-Picard-2021 commented 2 years ago

But then the old listtiset/2 had a different semantics again:

listtoset([], []).
listtoset([Head|Tail], Set) :-
    memberchk(Head, Tail), !,
    listtoset(Tail, Set).
listtoset([Head|Tail], [Head|Set]) :-
    listtoset(Tail, Set).

Here you see the difference:

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

?- listtoset([c,a,b,a], X).
X = [c, b, a].
jfmc commented 2 years ago

What do you mean by "just"? Do you say I can run .lgt files in the Ciao Prolog playground? I have clarified my question here:

(playground) Can I run Logtalk from within the new Ciao Prolog Playground? https://\github.com/ciao-lang/ciao/issues/64

No, you cannot run .lgt files in the Ciao Prolog playground because you cannot do either in the native Ciao Prolog toplevel (you can do if you install Logtalk).

I mean that the playground does not have a different set of libraries. So any problem with lists.pl is shared by the playground, Ciao for x86, Ciao for ARM, or Ciao for any platform.

Jean-Luc-Picard-2021 commented 2 years ago

You wrote above, which is possibly a wrong statement:

Note that the playground is not a separate Ciao implementation

Maybe you should have said Ciao WASM and not Ciao Playground. By Ciao Playground I am more refering to the Web Interface, and how it is configured by default. The default seems to be no support for Logtalk.

Sometimes its very difficult to find a common language, maybe there is also a language barrier. In some lingo the Ciao Playground would be called frontend. And the Ciao WASM, although it lands

on the client side, would be called backend. But you have anyway wrapped it in a worker dedicated as a Ciao WASM service, that acts as a kind of backend. What is not in your worker, how do you

call this? I really opened this ticket for the Ciao Plaground, and not for the whole Ciao Ecosystem. Maybe it would be more suitable to close this ticket and start all over,

if you want a ticket for the Ciao Ecosystem. I have the feeling the ticket was hijacked for something else. And I even don't know what this something else should be. And you did such a robbery already

on SWI-Prolog discourse, remember? All I want is to run this here:

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

In the Ciao Plaground, so that I can do some further performance testing of the Ciao WASM. But instead of a Web Interface a Command Line Interface (CLI) would be also ok, if Ciao WASM has already

been bundled this way.

Jean-Luc-Picard-2021 commented 2 years ago

I am already almost done with figuring out what is missing from Ciao WASM to run the fcube.p example, and could provide a subtract/3 polyfill for Ciao WASM, which would both run

in a terminal web interface and in a CLI access to the Prolog interpreter, since it only needs basic text I/O to a console. The current step is to decided on an implementation of list_to_set/2.

And it stroke me that the DEC 10 listtoset/2 has another semantics. Here is the actual progress, in figuring out what is missing. I have already resolved Jekejeke and SWI. And need

still to resolve Scryer and Ciao:

http://www.xlog.ch/izytab/moblet/docs/18_live/20_novacore/example62/package.html 185481520-8899dd89-48c0-4ba9-942a-6bc10f122f9c

Jean-Luc-Picard-2021 commented 2 years ago

BTW: The two terms Ciao WASM and Ciao Plaground are not my idea, its from the paper here:

https://cliplab.org/papers/scasp-web-gde.pdf

Unbenannt

jfmc commented 2 years ago

Jan, please focus the scope of your messages and stop adding confusion.

jfmc commented 2 years ago

I'm closing this issue since it diverted too much. It is not clear what is the purpose.