Careful with subtract/3

Trying to port fCube:

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

The porting turns out as a little night mare.

I find in SWI-Prolog:

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

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

And in Ciao Prolog, using the new online 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)}

Whats the reason for this discrepancy? Should I use dialect import
in Ciao Prolog? Does Ciao Prolog have dialect import? Is a SWI-Prolog
dialect supported? Or whats the cure for this desease?

Edit 14.08.2022
Its a little annoying, since this here, the union/3, works for example:

?- 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

As mentioned in Ciao github issue ((playground) Feature request subtract/3 ¡ Issue #60 ¡ ciao-lang/ciao ¡ GitHub): substract/3 is provided in the idlists module.

Ciao does not support SWI’s notion for dialects. AFAIK dialects were introduced in SWI during one of our Prolog Commons meetings. We will not support this notion of dialects because it is really confusing, error prone and really hard to implement without a precise description of what each dialect means. Emulating a frozen or dead system is doable, but Ciao is a moving target. It is hard to emulate Ciao or SWI or any other system without some coordination (that currently, does not exists).

What Ciao supported from the beginning is a module/3 directive where the 3rd argument specifies a list of packages. Packages are ‘glorified includes’ that group prolog flags, term expansions, operators, etc. local to that module. Rather than dialects, Ciao supports the idea of ‘features’ enabled/disabled by (user defined) packages and (as much as possible) local to each module.

It looks like simply a bug of that new playground, because the subtract-query seems too basic, which should be independent of any dialect.

It seems to have 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.
Identity lists — The Ciao System v1.22

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

I see. In fact, SWI-Prolog is the only programming language which I use. I am recognizing that comment was too narrow.

Ciao Prolog did some huge changes in the past. Changing the predicates in lists.pl would be trivial. Let just agree on what should be there and we can do it. There is no need to wait for Ciao2.

In fact, this seems the exact same definition as the subtract/3 in Ciao’s idlists library module (except the names of the variables are ABC instead of meaningful names).

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.

But this all does underline that we need better coordination for theses things (as @jmfc and also @jan have mentioned before).

Also I think the example needs maybe some small mending.
Maybe it cannot be done for all Prolog systems as is. For
example I find the following in Ciao Prolog:

?- tab(2*3+1).
{ERROR: No handle found for thrown exception 
error(type_error(integer,2*3+1),'io_basic:tab'/1-1)}
aborted

Whereas in SWI-Prolog I get:

?- tab(2*3+1).
       
true.

Which could be an unintended effect, by implementing it
with some arithmetic, don’t know. And then users start using it.
And then in Ciao Prolog it was implemented differently.

As far as I can tell that behavior is not standardized? If you want to do that in Ciao you can do it easily by loading the functional package, which adds functional syntax (which should not bother you otherwise) and also evaluation of arithmetic expressions:
?- use_package(functional).
…
yes
?- tab(2+2), write(a).
a
yes

Note that this version of subtract is loaded from a different library, where the difference in the treatment of variable is clearly stated, and therefore there is no clash, and in any case such differences can often be resolved using conditional code. It is also easy to simply include a definition for subtract within conditional code, that is active for just a particular Prolog. Having said that, giving the predicates in idlists separate names could also be an option.

(Nothing of importance here)

Regarding the comparison with Picat, take into account that Ciao’s extensions for functional syntax predates Picat by several years (https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.78.7221&rep=rep1&type=pdf, around 2006). I personally think that Picat ideas are great and Neng-Fa Zhou managed to combine loop syntax, action rules (related to CHR), functional syntax in a consistent way. The main difference is that all extensions are optional in Ciao. The “kernel” language underlying all Prolog implementations is exactly the same. Indeed we can use a “Ciao0” as you name it in modules by declaring that they do not use any “extension” at all. In that case it is closer to pure logic programs. All of this is beyond ISO Prolog, of course. Or claim is that on top of an extensible kernel we can implement both ISO and also many interesting Prolog extensions.

All these features should be available in Ciao WASM because WASM is just another POSIX-like platform (it is “free” as long as we make the modules available).

A similar approach is taken in Haskell (Language extensions - HaskellWiki) and this is important to drive the evolution of the language. That is, we should not be talking about Prolog dialects but about Prolog “features”. We have some idea of what are the default features that we want for our code (compilers, analyzers, etc.) or in a research paper showing some idea, but we are completely open about the features expected in “ISO Prolog mode”.

(Nothing of Importance here)

Our point is that ISO Prolog is not the right starting point for a kernel Prolog language. It has a lot of peculiarities (and libraries, and builtins) that go beyond depth-first search plus unification of Herbrand terms. Our base language is simpler than ISO and we add as much as possible on top of it.

We’d gladly discuss anything related to Ciao, its design, and philosophy, but perhaps it’d be better to continue on our GitHub discussions rather than on SWI’s Prolog discourse?

Actually, it is quite simple and there is no contradiction at all: in Ciao, the base language does not have most of the ISO prolog built-ins, they are in libraries. If you do not do anything, then the ISO built-ins are loaded by default and it behaves exactly as a standard Prolog, which is the intention and what many Ciao users see and use all the time. But Ciao also allows not loading the ISO built-ins (and then you are in pure Prolog, which is very useful for teaching) or even redefining them. For example:

BTW, If you want to talk about the limitations and weak points of Ciao Prolog, we can tell you, we are aware of them. If you want us to explain why we believe that some decisions in Ciao are good, we can do it. If something is not well documented, file and issue or better open a pull request. We are open source and admit contributions.

Exactly! There is definitely an (optimized) WAM there, and there is of course resolution, but you are not forced to use the the ISO built-ins if you do not wish to. And this happens on a per module basis. I.e., you can have all your program modules be ISO and then have a particular module in which you are using a new type of arithmetic instead of is/2, or functional syntax, or… It is additional functionality beyond ISO, with the quirk that you can add or subtract the ISO stuff at will. This is not meant of course for applications that want to be portable, where you probably want to stick to standard Prolog, but it is very useful to design new languages, future directions for Prolog, etc. and play with them in a module without affecting the overall system.

(Nothing of importance here)

Yes, you can do it no problem. You will get:

{Compiling /draft.pl
WARNING: (lns 2-5) Unqualified predicate call to tab/1 assumed to local version, calls to predicate imported from io_basic must be qualified
}

which means exactly that, i.e., that now you have two versions of tab/1, a local one and the one imported from the libraries. If you want to be able to call the one you defined from the top level, export it from the module (here draft.pl)

:- module(_,[main/0,tab/1]).

main :- 
    tab(4),
    write(a).

tab(X) :- Y is X, io_basic:tab(Y).

and now:

?- use_module('/draft.pl').
{Compiling /draft.pl
WARNING: (lns 2-5) Unqualified predicate call to tab/1 assumed to local version, calls to predicate imported from io_basic must be qualified
}
yes
?- draft:tab(3+2), write(a).
     a
yes

If you want to avoid the warning when compiling the module use:
:- redefining(tab/1).

In the top level:

?- use_module('/draft.pl').

yes
?- draft:tab(3+2), write(a).
     a
yes

[ A brief reading guide for this thread, or ‘how we ended up here?’:

  • You mentioned that it would be hard for Ciao to change the lists module.
  • We explained that the Ciao design make this simple (so we can do it, but we need agreements on the changes because adding one predicate here may break some other source there)
  • To explain the Ciao design we need to say that in Ciao very few predicates are “builtin” (we can enable/disable a lot of things in the language). This is irrelevant for the original discussion but needed, since you said that doing changes in Ciao would be hard. ]