Expects_dialect(sicstus): how to handle SICStus 3 vs. 4 API conflicts

I’m still working on getting a SICStus-based application to run on SWI using expects_dialect(sicstus) and am extending SWI’s library(dialect/sicstus) in the process. At the moment, SWI’s library(dialect/sicstus) seems to provide almost only SICStus 3 predicates/libraries, so I started (locally) implementing various SICStus 4-only predicates/libraries that are needed by the application I’m working on. However, I ran into an issue with trying to add SICStus 4 support to SWI’s library(dialect/sicstus) while keeping the existing SICStus 3 support.

Many APIs are identical in SICStus 3 and 4 or were only slightly renamed, but some APIs have changed significantly between SICStus 3 and 4, for example the file system interaction API. On SICStus 3, library(system) provided a few file system predicates like file_exists, make_directory, rename_file, delete_file, etc. On SICStus 4, the file system API has been moved out of library(system) and completely redesigned as a separate library(file_systems). One of the major changes is that library(file_systems) treats files and directories as completely different things. For example, on SICStus 3, delete_file from library(system) could delete both files and directories, whereas on SICStus 4, library(file_systems) provides separate delete_file and delete_directory predicates that accept only regular files or only directories.

When I added a library/dialect/sicstus/file_systems.pl in my local SWI build to emulate the SICStus 4 library(file_systems), I ran into the problem that I couldn’t import both library(system) and library(file_systems) at the same time, because some of the SICStus 3-compatible file system predicates from library(system) conflicted with SICStus 4 library(file_systems) predicates with the same names:

?- expects_dialect(sicstus).
true.

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

?- use_module(library(file_systems)).
ERROR: import/1: No permission to import file_systems:rename_file/2 into user (already imported from system)
ERROR: import/1: No permission to import file_systems:file_exists/1 into user (already imported from sicstus_system)
ERROR: import/1: No permission to import file_systems:delete_file/1 into user (already imported from system)
true.

On real SICStus 4 this works without problems, because SICStus 4 library(system) no longer provides the SICStus 3 file system predicates:

| ?- use_module(library(system)).
% loading .../bin/sp-4.5.1/sicstus-4.5.1/library/system.po...
% module system imported into user
% ...
% loaded .../bin/sp-4.5.1/sicstus-4.5.1/library/system.po in module system, 6 msec 34656 bytes
yes
| ?- use_module(library(file_systems)).
% loading .../bin/sp-4.5.1/sicstus-4.5.1/library/file_systems.po...
% module file_systems imported into user
% ...
% loaded .../bin/sp-4.5.1/sicstus-4.5.1/library/file_systems.po in module file_systems, 4 msec 186464 bytes
yes

I’m not sure what would be the best way to handle this. I can’t just merge the definitions of the conflicting predicates (and have one module import it from the other), because for example with delete_file the behavior differs between the two versions/libraries (see above). I need some way to have use_module(library(system)) import only the SICStus 4-compatible predicates.

SICStus 4 still provides the SICStus 3 libraries, just renamed with a 3 at the end - e. g. SICStus 4 library(system3) is SICStus 3 library(system). SWI’s SICStus emulation could do the same, although this would break some existing code relying on the SICStus 3 emulation. It would also be possible to separate emulation for the two versions completely, i. e. have both expects_dialect(sicstus3) and expects_dialect(sicstus4) (with expects_dialect(sicstus) redirecting to sicstus3 for compatibility?). Or possibly the SICStus 3 support could be removed entirely in favor of SICStus 4 (I have no idea how much SICStus 3 is still used in practice).

Good questions. I’m tired after too much Zoom today so this is a quick answer. I may have misread some of the details.

I can give you one answer for sure: we do not want to drop SICStus3 as this emulation has been used by a couple of projects who reasoned when they had to migrate anyway from SICStus 3, why not to SWI-Prolog instead of SICStus 4 :slight_smile:

I wonder whether you can get away with use_module/2 to remain compatible and get the file predicates from the intended library?

Else, I’d consider adding a sicstus4.pl file to the dialect that sets a Prolog flag sicstus4 or similar and then loads sicstus.pl. Now you can use :- if, etc. to make necessary conditional changes. Would that work?

Another trick could be to have a sicstus4 library directory that only contains the stuff that is different and push this directory as first in the search path, so the search path is sicstus4, sicstus and then the SWI default.

More SICStus 4 emulation is surely welcome! Thanks so far.

Thank you for the fast reply!

OK, good to know - that makes sense.

Yes, that’s an option as well. Almost all of our code that imports library(system) only needs environ/2 anyway, so it wouldn’t be hard to add the appropriate import lists everywhere. But at the moment, whenever I run into a compatibility issue that I could solve by modifying our code, I try to see how difficult it would be to make expects_dialect(sicstus) handle it automatically instead. The ideal situation would be “just put :- expects_dialect(sicstus). before your SICStus code and then everything works on SWI”, and I’m trying to get as close to that as is reasonably possible.

I think I’ll try something with a separate sicstus4 directory next. The simplest solution would probably be to just add a new emulated dialect named sicstus4, which provides all SICStus 4-specific predicates and reexports predicates from library/dialect/sicstus when they haven’t changed between SICStus 3 and 4. This way there would be no need for a new global Prolog flag or an extra directory on the search path. I’ll see how well this works out.

1 Like

Appreciated :slight_smile: In most cases I take a more pragmatic position, also changing clear SICStus way of doing things to something that also works in SICStus, but is way easier to support in SWI-Prolog. Notably there are cases where some SICStus specific bit is easily rewritten to something that works on both systems.

I think that may work. Looking forward!

1 Like

subsumes_term/2 is part of one of the ISO extension and does not bind. The SWI-Prolog implementation is semantically as below, although the actual implementation is entirely in C.

subsumes(General, Specific) :-
	term_variables(Specific, SVars),
	General = Specific,
	term_variables(SVars, SVars).

subsumes_term(General, Specific) :-
    \+ \+ subsumes(General, Specific).

And thus:

?- when(nonvar(X), X=a), subsumes_term(X, b).
false.

The issue seems to be whether or not subsumes_term/2 must execute constraints, where SWI-Prolog does so and SICStus appears to not trigger the constraints. I guess there are arguments for either solutions and no ISO god to tell us the verdict.

Oh, and the current version has both a sicstus and sisctus4 dialect thanks to @swi. The only problem is that it is pretty hard (is it even possible?) to realise the SICStus behavior in pure Prolog.

edit

I think the SICStus way looses some important properties of subsumes_term/2: subsumes_term/2 succeeding implies the two terms can be unified and both become equivalent to the specific term which implies that specific remains unchanged. By not evaluating the constraints in subsumes_term/2 the subsequent unification may fail and the constraints may further instantiate the specific term.

On the other hand, the SICStus way is consistent with =@=/2 (variant/2) which ignores attributes. But then, I have no clue on the “right” semantics given constraints, while for subsumes_term/2 we can define a sensible semantics.

it was someone else that contributed this code :grin:, don’t know who did it though.

Sorry. @dgelessus, see Expects_dialect(sicstus): how to handle SICStus 3 vs. 4 API conflicts

Only did some very quick testing, but it seems that simply removing all attributes (using copy_term_nat/2) before calling subsumes_term/2 matches the SICStus behavior wrt attributes and constraints:

sicstus_subsumes_term(General, Specific) :-
    copy_term_nat((General, Specific), (GeneralClean, SpecificClean)),
    subsumes_term(GeneralClean, SpecificClean).

All of the examples from the SICStus documentation work as expected (by SICStus) with this implementation:

?- sicstus_subsumes_term(a, a).
true.
?- sicstus_subsumes_term(f(X,Y), f(Z,Z)).
true.
?- sicstus_subsumes_term(f(Z,Z), f(X,Y)).
false.
?- sicstus_subsumes_term(g(X), g(f(X))).
false.
?- sicstus_subsumes_term(X, f(X)).
false.
?- sicstus_subsumes_term(X, Y), sicstus_subsumes_term(Y, f(X)).
true.
?- when(nonvar(X), X=a), sicstus_subsumes_term(X, b), X = a.
X = a.
?- when(nonvar(X), X=a), sicstus_subsumes_term(X, b), X = b.
false.

Not sure if this counts as “pure Prolog”, because copy_term_nat/2 isn’t supported by some dialects, like SICStus for example :slight_smile: But for use in SWI’s emulation that wouldn’t be a problem.

Clever :slight_smile: At least we know how to solve it should it ever be needed.

There are roughly twp possible semantics:

  • unify_with_occurs_check/2 does not create any new cycles
  • After unify_with_occurs_check/2 the term is acyclic.

SWI-Prolog implements the first. Most systems seem to do the latter. The simplest distinguishing case is

?- X = s(X), unify_with_occurs_check(X, X).
X = s(X).

I don’t recall what the standard says.

IMHO, unify_with_occur_check is to guarantee the completeness
of the resolution principle over Herbrand interpretation (the well-founded ground terms), but it is not necessary for completeness of that over rational tree domain (cyclic ground terms). However, the first one (SWI) is a conservative extension, I guess, of the second. So my preference is to the first, though I don’t know what is the practical purpose of this extension.

It is mostly a practical consequence of set_prolog_flag(occurs_check, true). If this had to prove a term is acyclic after every unification we get a huge slowdown. In practice, most compiled unification can avoid the general unification routine and know they do not introduce cycles. They can not guarantee no cycle exists. Now, unify_with_occurs_check/2 does the same, both for efficiency (it has to check less in many cases) and for consistency.

Note that, if no cycles exist, the SWI-Prolog model guarantees they are not created and thus we stay within the Herbrand world.

I don’t think anyone would try to achieve that. The emulation layer is mostly to provide enough common ground to make it feasible to write an application that runs on both with not too many hacks in the code itself. That typically requires using predicates “as they are intended” rather than trying to find the edge cases. In most cases the above will make no difference as you typically use unify_with_occurs_check/2 in cases where you would like to avoid creating a cyclic term. In those cases where cycles may be created at several places and you use this predicate to check there are no cycles in a term, simply unify and call acyclic_term/1.

I imagine a case in which one wants to handle a mixed data structure consisting of well-founded-terms and non-well-founded-terms. If one could specify (declare) such mixed structures in some type declaration, unify_with_occur_check might be used to prevent well-founded-components from getting cyclic accidentally, though I have no concrete example. Anyway I am amateur on this.

I guess the answer is not. Practically the only sensible solution is to do program transformation that replaces all non-sound head unifications with unify_with_occurs_check/2 and all explicit unifications with this. That is quite hard to do for full Prolog.

But then, you cannot emulate delimited continuations (reasonably), you cannot emulate engines, threads, etc. Even JIT indexing is really hard to emulate. You can only emulate stuff that is roughly available at the other side or can easily expressed in more low level stuff.