Closed UWN closed 2 years ago
Why not ask for change_arg/3
. You can bootstrap a lot
of usuful things with change_arg/3
alone. Here is my take
on call_nth/2
as done for Dogelog Player:
/**
* call_nth(G, C):
* The predicate succeeds whenever G succeeds and unifies C with
* the numbering of the successes.
*/
% call_nth(+Goal, -Integer)
call_nth(G, C) :- var(C), !,
call_nth2(G, N),
C = N.
call_nth(G, C) :-
C > 0,
call_nth2(G, N),
(C =:= N -> !; fail).
% call_nth2(+Goal, -Integer)
call_nth2(G, N) :-
Holder = v(0),
G,
arg(1, Holder, M),
N is M+1,
change_arg(1, Holder, N).
Works fine:
?- call_nth((X=a;X=b), N).
X = a, N = 1;
X = b, N = 2.
Ok, you know this implementation anyway,
but nobody promotes change_arg/3
, why is this so?
count the number of calls of a clause https://stackoverflow.com/a/11400256/17524790
In formerly Jekejeke Prolog the trick with the extra variable
doesn't work, i.e. State=count(0,_)
, but functor(State, count, 1)
works in next release. I don't know what works for ichibans Go Prolog.
Providing destructive assignment has many negative effects. It results in many implementation dependent effects that practically prevent more advanced techniques. Both statically and dynamically.
Consider the fact
f(g(h(c)), h(c)).
this might be compiled into
f(g(X),Y) :- X=h(c), X = Y.
With destructive assignments present, such optimizations change the meaning of programs.
If you look into existing implementations, there are only a few that permit general destructive assignment (SWI), many provide more limited, much better defined forms (SICStus, Eclipse). And some just provide call_nth/2
like Trealla and Scryer.
Term representation becomes a bit visible when writing unnamed variables (?- writeq(X-X).
) and in term comparison. With destructive assignment things become much worse.
The easiest way out is just to provide call_nth/2
and to defer all other considerations to a later moment.
If you don't think about introducing change_arg/3
in your Prolog system
head start first, and start implementing call_nth/2
and all other stuff instead
first, you are doing something wrong. The design flaw is seen in Scryer
Prolog which has a much slower call_nth/2 now:
/* Scryer Prolog */
?- time((between(1,1000,_), call_nth(call_nth((X=a;X=b), N), M), fail; true)).
% CPU time: 1.010s
true.
On the other hand in Dogelog Player I get, and I even don't need
any expensive setup_call_cleanup/3
in its implementation:
/* Dogelog Player */
?- time((between(1,1000,_), call_nth(call_nth((X=a;X=b), N), M), fail; true)).
% Wall 61 ms, gc 0 ms, 837475 lips
true.
Or as Trump said: "If it works, its not broken". You can mark the built-in as internal only, and warn the ordinary end-user to not use it, until the end-user exactly knows what he is doing.
Actually Trump said: "Sounds good, doesn't work". But change_arg/3
is exactly the converse. It excels above all!!! In the above Dogelog Player
is 16 times faster. But I nowhere advocate making change_arg/3 a
novice Prolog programmer predicate. I even don't know whether its possible in Scryer Prolog or in ichiban/prolog. Also change_arg/3 is usally simpler to use for atomic Prolog terms than for non-atomic
Prolog terms. So a strategy could be to first experiment with change_arg/3 that can update atomic replacements. Later things can indeed become complicated, for example SWI-Prolog has two different copy_term/2.
Also that change_arg/3 isn't widely available is not correct, since recently I have it in formerly Jekejeke Prolog. So the list is bigger:
I didn't make a comprehensive survey yet. For Dogelog Player and formerly Jekejeke Prolog, concerning the predicate name, I am orienting myself on BinProlog Paul Tarau.
As to SICStus and ECLiPSe, you could see their highly restricted ways providing such functionality in the link to SO that you posted. They do not provide the generality of setarg. There used to be an (undocumented) setarg in earlier versions of SICStus which was according to the sources "Put in at the express request of" some person. And it only worked for one cons-cell. As for GNU, it does not have garbage collection...
Oops, yes my bad. It could be that SICStus Prolog and ECLiPSe Prolog do not have some change_arg/3 equivalent. Was also making an experiment with:
call_nth2(Goal_0, C) :-
State = v(0),
Goal_0,
arg(1, State, C1),
C2 is C1+1,
nb_linkarg(1, State, C2),
% setarg(1, State, C2, false), % for GNU Prolog
C = C2.
And then I got:
/* SWI-Prolog */
?- time((between(1,1000000,_),
call_nth2(call_nth2((X=a;X=b),N), M), fail; true)).
% 10,000,003 inferences, 0.859 CPU in 0.847 seconds
(101% CPU, 11636367 Lips)
true.
/* GNU Prolog */
?- ((between(1,1000000,_),
call_nth2(call_nth2((X=a;X=b),N), M), fail; true)).
(1578 ms) yes
Was I allowed to use nb_linkarg/3? If this is allowed, then SWI-Prolog
ranks top in speed. Same speed as ECLiPSe Prolog which doesn't
need setup_call_cleanup/3
, solution from here:
/* ECLiPSe Prolog */
[eclipse 5]: between(1,1000000,_), call_nth(call_nth((X=a;X=b), N), M), fail; true.
X = X
N = N
M = M
Yes (0.84s cpu)
But 10 times faster than SICStus Prolog, which needs setup_call_cleanup/3
,
solution also from here, which gives quite a speed damping:
/* SICStus Prolog */
?- statistics(walltime, A), (between(1,1000000,_), call_nth(call_nth((X=a;X=b), N), M), fail; true),
statistics(walltime, B).
A = [408655,137987],
B = [416794,8139] ?
@UWN Thank you for letting me know this! I've learnt that the community hasn't agreed on what nth
really means in Prolog https://github.com/ichiban/prolog/issues/160#issuecomment-1068351595 so I'll implement call_nth/2
as an extension and make it available in 1pl
.
@Jean-Luc-Picard-2021 Thank you for sharing change_arg/3
and others! I'm afraid we're not going to support them, though. It might make sense for standalone Prolog processors to have such a destructive predicate but this one is an embeddable processor so you can always let the host language, Go, do the destructive operation.
Here's an implementation of change_arg/3
for this library: https://go.dev/play/p/eKhZ-LucGMQ
package main
import (
"os"
"github.com/ichiban/prolog"
"github.com/ichiban/prolog/engine"
)
func main() {
p := prolog.New(nil, os.Stdout)
p.Register3("change_arg", ChangeArg)
if err := p.QuerySolution(`X = f(a, b ,c), change_arg(2, X, d), write(X).`).Err(); err != nil {
panic(err)
}
}
func ChangeArg(n, term, newValue engine.Term, k func(*engine.Env) *engine.Promise, env *engine.Env) *engine.Promise {
var i int
switch n := env.Resolve(n).(type) {
case engine.Variable:
return engine.Error(engine.ErrInstantiation)
case engine.Integer:
if n < 0 {
return engine.Error(engine.DomainError("not_less_than_zero", n))
}
i = int(n) - 1
default:
return engine.Error(engine.TypeErrorInteger(n))
}
var c *engine.Compound
switch t := env.Resolve(term).(type) {
case engine.Variable:
return engine.Error(engine.ErrInstantiation)
case *engine.Compound:
c = t
default:
return engine.Error(engine.TypeErrorCompound(t))
}
if i < 0 || i >= len(c.Args) {
return engine.Bool(false)
}
c.Args[i] = newValue
return k(env)
}
@UWN I implemented call_nth/2
. Could you check if it works, please?
$ git checkout main
Already on 'main'
Your branch is up to date with 'origin/main'.
$ git pull
remote: Enumerating objects: 5, done.
remote: Counting objects: 100% (5/5), done.
remote: Compressing objects: 100% (5/5), done.
remote: Total 5 (delta 0), reused 0 (delta 0), pack-reused 0
Unpacking objects: 100% (5/5), 36.08 KiB | 4.01 MiB/s, done.
From github.com:ichiban/prolog
c9131d7..d196e2e main -> origin/main
Updating c9131d7..d196e2e
Fast-forward
cmd/1pl/interpreter.go | 13 +++++++++++++
cmd/1pl/interpreter_test.go | 61 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
cmd/1pl/main.go | 2 +-
codecov.yml | 2 ++
engine/builtin.go | 40 ++++++++++++++++++++++++++++++++++++++++
engine/builtin_test.go | 82 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
6 files changed, 199 insertions(+), 1 deletion(-)
create mode 100644 cmd/1pl/interpreter.go
create mode 100644 cmd/1pl/interpreter_test.go
create mode 100644 codecov.yml
$ go install github.com/ichiban/prolog/cmd/1pl
$ $(go env GOPATH)/bin/1pl
Top level for ichiban/prolog (devel)
This is for testing purposes only!
See https://github.com/ichiban/prolog for more details.
Type Ctrl-C or 'halt.' to exit.
?- call_nth((N = 1; N = 2), Nth).
N = 1,
Nth = 1;
N = 2,
Nth = 2;
?-
This predicate is particularly useful for testing purposes.