ichiban / prolog

The only reasonable scripting engine for Go.
MIT License
564 stars 27 forks source link

Modules? #292

Open ichiban opened 1 year ago

ichiban commented 1 year ago

The Quintus module system looks like the de facto standard, yet I found that there's a slight problem adopting it. Its modules are coupled with files (module files) and use_module/[1,2,3] take filenames as an argument.

In this library, a Prolog text doesn't have to be in a file. So, if we define a module in Exec(), we can't import the module with use_module/[1,2,3]. Also, a Go-defined module can't be imported with use_module[1,2,3] because it doesn't have a module file.

p := prolog.New(nil, nil)
p.Exec(`
:- module(foo, [hi/0]).
hi :- write(hi), nl.
`)
p.Exec(`
:- use_module(???).
:- initialization(hi).
`)

We might also need import/[1,2] in ISO/IEC 13211-2:2000 to avoid this.

p := prolog.New(nil, nil)
p.Exec(`
:- module(foo, [hi/0]).
hi :- write(hi), nl.
`)
p.Exec(`
:- import(foo, [hi/0]).
:- initialization(hi).
`)
guregu commented 1 year ago

It would be awesome to have modules!

Some thoughts: It would be nice to be compatible with Scryer and Trealla. There is now a small ecosystem for modern ISO Prologs and it would be great if we could all share libraries. Maybe Go-defined modules could be put in the library "namespace", so you import them like: :- use_module(library(json)). For modules defined by Exec, maybe we could treat them as if they were in the root? We would have to keep track of them as a kind of layer on top of the real filesystem. Could be something as simple as a map[string]Module.

So the use_module logic could go like this for use_module(foo):

  1. Has the module foo been defined by Exec? If so, use it.
  2. Otherwise, does foo.pl exist in the root of the filesystem? Or the current folder relative to this module? If so, read and use it.
  3. Otherwise, fail.

Maybe 2 shoud go before 1 here, I'm not sure what the ideal priority would be.

ichiban commented 1 year ago

Regarding the problem on Exec(), we could treat Exec(<Prolog Text>) same as Exec(":- ['/path/to/foo.pl'].") where /path/to/foo.pl contains the given Prolog text. That way, all the exported predicates will be imported.

p := prolog.New(nil, nil)
p.Exec(`
:- module(foo, [hi/0]).
hi :- write(hi), nl.
`)
p.Exec(`
:- initialization(hi).
`)
ichiban commented 1 year ago

use_module/3 might be appropriate for Exec().

p := prolog.New(nil, nil)
p.Exec(`
:- module(foo, [hi/0]).
hi :- write(hi), nl.
`)
p.Exec(`
:- use_module(foo, _, [hi/0]).
:- initialization(hi).
`)
UWN commented 1 year ago

SICStus (which is also the successor of Quintus, the originator of SICStus modules) is definitely best to follow. A true weakness in SICStus is that all operators are global, but then this leads to a more conservative usage of operators. Scryer mostly follows SICStus but permits operators to be local or exported.

SWI has some mixed-up system which has received some SICStus compatibility about 10 years ago. But there are still differences. In case of doubt, go for SICStus. Sometimes SWI looks better because it adds some module prefixes dynamically, this comes at a cost in particular for goal expansion.

ISO permits a lot of instances of different module systems. Within 13211-2 there are already two (the one you seem to mean, and in 6.4.4.2 IF/Prolog's). Even SICStus could be seen as such an instance (which at first sight is something different, but... it's complicated).

ichiban commented 1 year ago

Placeholder ? will conflict with meta predicate mode indicator ?.

if err := p.Exec(`human(?).`, "socrates"); err != nil { // Same as p.Exec(`human("socrates").`)
    panic(err)
}
UWN commented 1 year ago

What is the purpose of these placeholders? I note that they seem to be present at the top level. Are they also present in other situations?


?- A = ? .
2023/07/15 08:12:37 failed to query: not enough arguments for placeholders
?- char_code(C,0'?).
C = ?;
?- 
|- char_code(C,0'?), call(C=X).
C = ?,
X = ?;
ichiban commented 1 year ago

I've implemented placeholders to make it safe and easy to pass Go values to Prolog. Also, it helps providing a standard database/sql-like API. Both make it approachable for gophers, I hope.

Currently, It's present in every query and prolog text. We can change the code and suppress it for queries/prolog texts without extra Go arguments. That way, we'll be able to use ? as a normal atom at the top level and in module files.

UWN commented 1 year ago

So you say, your top level is special, but otherwise, the ? is treated just as an atom? That is with another top level, this problem would not show? In this case there would be no reason to change, as the top level is out of scope of the standard. See 1 Scope Note f.

ichiban commented 1 year ago

I mean, ? is special everywhere. It reads ?, in a prolog text or top level, as an atom but immediately tries to replace it with a Go argument even if none is given.

This can be easily fixed with the change I described above.

ichiban commented 1 year ago

What's in a module?

predicates operators char_conversion flag char_conversion flag debug flag unknown flag double_quotes
ISO/IEC 13211-2 ✔️ ✔️ ✔️ ✔️ ✔️ ✔️ ✔️
SICStus 4.8.0 ✔️ :x: [^1] :x: [^2] :x: [^3] :x: [^3] :x: [^3] :x: [^3]
SWI 9.0.4 ✔️ ✔️ ^4 :x: :x: :x: ✔️ [^5] ✔️ [^6]
Scryer 0.9.1 ✔️ ✔️ ? ? ? :x: :x:

[^1]: "operators are global, as opposed to being local to the current module, Prolog text, or otherwise." [^2]: "the mapping is global, as opposed to being local to the current module, Prolog text, or otherwise." [^3]: "Prolog flags are global, as opposed to being local to the current module, Prolog text, or otherwise."

[^5]: "This flag is local to each module" [^6]: "maintained for each module"

ichiban commented 1 year ago

writeq/2 is a context sensitive built-in [^1] and can be bootstrapped from write_term/3. [^2]

ISO/IEC 13211-2 6.2 says "built-in predicates and control constructs are visible everywhere and do not require module qualification." To achieve this, SICStus and others have a special module for control constructs and built-in predicates for each module to import from.

The other predefined module is the prolog module where all the built-in predicates reside. https://sicstus.sics.se/sicstus/docs/latest4/html/sicstus.html/ref_002dmod_002dbas.html

I found a problem here. If we bootstrap writeq/2 from write_term/3 in module prolog, the calling context for write_term/3 becomes prolog and it will lookup operators from prolog instead of the calling context for the writeq/2.

This won't be a problem in SICStus bc its operators don't belong to modules. I should check how other implementations solve it.

:- use_module(prolog, [...]).

writeq(S, Term) :- 
  write_term(S, Term, [quoted(true), numbervar(true)]).  % The calling context is `prolog`.

[^1]: ISO/IEC 13211-2 6.4.2.b [^2]: ISO/IEC 13211-1 8.14.2.5

UWN commented 1 year ago

Most of the time operators are local because they are just needed within this module. I am not sure that it makes sense to make writeq/1 sensitive to it.

Look at SWI:

?- use_module(library(clpfd),[]).
true.

?- X #= Y.
ERROR: Syntax error: Operator expected
ERROR: X
ERROR: ** here **
ERROR:  #= Y . 
?- clpfd: #=(X,Y).
X = Y,
clpfd:in(Y, ..(inf, sup)). % so far everything is as expected

?- module(clpfd).
true.

clpfd:  ?- X#=Y.
X = Y,
in(Y, ..(inf, sup)).   % so why is there now no .. operator?
ichiban commented 1 year ago

If I read it right, ISO/IEC 13211-2 says writeq(#=(X,Y)) results in _2270#=_2272 in module clpfd. (ISO/IEC 13211-2 5.2.1.(3)) It makes sense to my amateur eyes because you can use op/3 to format outputs inside the module.

SWI's write_term/3 looks up the operators from user by default, which is different from read_term/[2,3] which look up from the current 'source module' by default.

$ swipl
Welcome to SWI-Prolog (threaded, 64 bits, version 8.2.4)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.

For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).

?- use_module(library(clpfd),[]).
true.

?- module(clpfd).
true.

clpfd:  ?- writeq(#=(X,Y)).
#=(_2270,_2272)
true.

clpfd:  ?- current_output(S), write_term(S, #=(X,Y), [module(clpfd)]).
_3740#=_3742
S = <stream>(0x104a6e7b8).
UWN commented 1 year ago

Just a general observation on 13211-2, I think I mentioned it somewhere already. Please look at 6.4.4.2 which shows you an entirely different module system. So 13211-2 is not as specific and as precise as you seem to interpret it. And, in case of doubt, leaning toward SICStus is definitely a safer bet.

ichiban commented 1 year ago

I'm still in a process of learning what module is in Prolog and using ISO/IEC 13211-2 as one of the resources. I'm not following it word by word anyways. One thing I learnt from it is a module has not only predicates but also operators and flags.

Regarding operators and flags, SICStus looks an outlier. I should check more implementations though. I don't feel that it is a safe bet to follow SICStus on this particular matter so far.

UWN commented 1 year ago

ISO/IEC 13211-2 was published 2000. Even in 2006, many of the aspects of relevance where not yet understood. Think of compatibility with call/N. And the only system that implemented 6.4.4.2 was IF (already in 1996). 6.4.4.1 was never implemented anywhere. You can see from the syntax error in the second line that at least that code never ran on a 13211-1 conforming processor.

ichiban commented 1 year ago

With this module modop, I think a query modop:wq(<>(a, b)) should result in a<>b. Only Ciao does so.

:- module(modop, [wq/1]).
:- op(700, xfx, <>).

wq(X) :-
    writeq(X).

SWI

$ swipl
Welcome to SWI-Prolog (threaded, 64 bits, version 8.2.4)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.

For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).

?- [modop].
true.

?- modop:wq(<>(a, b)), nl.
<>(a,b)
true.

Scryer

$ scryer-prolog
?- [modop].
   true.
?- modop:wq(<>(a, b)), nl.
<>(a,b)
   true.

Trealla

$ ../trealla/tpl
Trealla Prolog (c) Infradig 2020-2023, v2.24.19
?- [modop].
   true.
?- modop:wq(<>(a, b)), nl.
<>(a,b)
   true.

Ciao

$ ~/.ciaoroot/v1.22.0-m7/build/bin/ciao
Ciao 1.22.0 [DARWINaarch64]
?- [modop].

yes
?- modop:wq(<>(a, b)), nl.
a<>b

yes
UWN commented 1 year ago

You are "importing" the module modop via '.'/2, that is [File]. Nowhere in 13211-2 is this operation specified. And then, you are using explicit qualification, which when used directly is just a goto between modules. No visibility rules apply.

For the specific example:

First look whether or not <> is now defined in the default module. In SWI, it is considered local and thus is not defined. In Ciao it is now defined in the default module, so that might be the reason it is used later on.

SWI:

?- current_op(Pri,Fix,<>).
false.

?- current_op(Pri,Fix,modop:(<>)).
Pri = 700,
Fix = xfx.

?- module(modop).
true.

modop:  ?- current_op(Pri,Fix,<>).
Pri = 700,
Fix = xfx.

I cannot see such a distinction in Ciao.

Also, how would you implement a wqnl/1 as a utility predicate that should behave like writeq(T),nl? You would only use the operators as defined in the utility module.

ichiban commented 1 year ago

Thank you for the correction. Ciao's operators are not local to modules, I guess. I'm a bit surprised that none of the implementations do it as I expected- I don't understand Prolog modules at all.

Below is my hallucinated interpretation:

A utility wqnl/1 is similar to writeq/1- they're both bootstrapped (13211-1 8.14.2.5) and also context sensitive (13211-2 6.4.2). This combination asks processors to have some mechanism to make a predicate context sensitive. That led me to a search for the mechanisms in other implementations In https://github.com/ichiban/prolog/issues/292#issuecomment-1677241225.

I found SWI had calling_context/1 (also in 13211-2 6.4.4.2). With calling_context/1, we should be able to define wqnl/1 as a utility term I/O predicate:

wqnl(X) :-
  calling_context(M),
  M:writeq(X),
  nl.

Also, writeq/1 should be able to be defined in the same manner:

writeq(Term) :-
  calling_context(M),
  current_output(S),
  M:writeq(S, Term).

writeq(Stream, Term) :-
  calling_context(M),
  M:write_term(Stream, Term, [quoted(true), numbervars(true)]).

You can try the current module implementation with calling_context/1 now:

$ go install github.com/ichiban/prolog/cmd/1pl@module
go: downloading github.com/ichiban/prolog v1.1.4-0.20230818110238-9673e7fb4a9e
$ $(go env GOPATH)/bin/1pl
Top level for ichiban/prolog v1.1.4-0.20230818110238-9673e7fb4a9e
This is for testing purposes only!
See https://github.com/ichiban/prolog for more details.
Type Ctrl-C or 'halt.' to exit.
?- calling_context(M).
M = user.
?- 
UWN commented 1 year ago

It really is a good idea to just stick to SICStus. In addition, local operators and the ability to export operators from a module. So like in Scryer. But no more than that. What you call now calling_context/1 in SWI comes from its previous module system which has been given up. So it is really a waste of time to look into this. Why simulate some arcane properties.

ichiban commented 1 year ago

I'm trying to figure out what SICStus module system really is.

Unlike ISO/IEC 13211-2, it looks to me like module as a compilation unit- directives are there for telling how to read and compile the module file and no effect at run-time. (This could be because of my misunderstanding of ISO/IEC 13211-1 7.4.2.b, a directive specifies "the format and Syntax of read-terms in Prolog text.")

My hunch is that the key is lack of context sensitivity (other than meta predicates) at run-time in contrast of context-sensitive directives at compile-time. So, predicates use_module/[1, 2, 3] should always import predicates into user.

:- module(foo, [init/0, foo/0]).

init :- use_module(bar).

foo.
:- module(bar, [bar/0]).

bar.
SWI is different here and Ciao didn't work as is yet Scryer and Trealla did it as I expected. ``` $ swipl Welcome to SWI-Prolog (threaded, 64 bits, version 8.2.4) SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software. Please run ?- license. for legal details. For online help and background, visit https://www.swi-prolog.org For built-in help, use ?- help(Topic). or ?- apropos(Word). ?- use_module(foo). true. ?- init. true. ?- bar. ERROR: Unknown procedure: bar/0 ERROR: However, there are definitions for: ERROR: var/1 false. ?- ``` ``` $ ~/.ciaoroot/v1.22.0-m7/build/bin/ciao Ciao 1.22.0 [DARWINaarch64] ?- use_module(foo). yes ?- init. yes ?- bar. {ERROR: user:bar/0 - existence error: procedure:user:bar/0 does not exist} aborted ``` ``` $ ../trealla/tpl Trealla Prolog (c) Infradig 2020-2023, v2.24.19 ?- use_module(foo). true. ?- init. true. ?- bar. true. ?- ``` ``` $ scryer-prolog ?- use_module(foo). true. ?- init. true. ?- bar. true. ?- ```
UWN commented 1 year ago

This usage is not the most common one. So I would not be surprised if there are differences maybe also within the same system. In fact, use_module should be seen rather as a directive and not as a goal.

On the other hand, looking at SICStus it has a meta predicate declaration for use_module/1 as well. But with a : which means that it is not a simple goal like 0 or one lacking one argument, as in 1 etc, but simply something that needs that module information. And thus this goal use_module(bar) is expanded into use_module(foo:bar). So the context is reestablished.

| ?- listing(foo:init).
foo:init :-
        use_module(foo:bar).

(I added a :- dynamic(init/0). directive to get this)

(As a general remark, it really helps to state explicitly what you expect or not. Currently it is clear to me, but some years later it may not.)

UWN commented 1 year ago

SICStus has the notion of a type-in module which can be changed with set_module/1 (since 4.0.0, before it was module/1) or the corresponding flag typein_module (not sure when this flag was added, at least since 3.8.5).