Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Answer Sources in Prolog (SWI) - Preview

485 views
Skip to first unread message

Julio Di Egidio

unread,
Sep 2, 2015, 10:09:47 PM9/2/15
to
Hi all,

I have implemented an initial version of Answer Sources in Prolog (SWI).

For the rationale and design, I have followed almost exactly Paul Tarau on
"fluent sources" [*], with at least the following differences:

- Our engines use multi-threading unlike Tarau's;
- Our engines execute arbitrary Prolog goals, i.e. are not restricted to
Horn Clauses;
- Thanks to threading, our 'next' operation ('get' in Tarau's) supports an
asynchronous pattern: e.g. this allows easy implementation of parallelism in
combinators;
- Our sources implement a 'reset' operation to restart the enumeration, so
Tarau's 'split' combinator is not necessary;
- The overhead of threading being unnecessary for combinators, basic
support for combinators is built in to the source object (via overloading);
- Our answer term extends Tarau's to report determinism.

=== These are the public declarations:

:- module(nan_kernel,
[ source_exists/2, % (+, ?) is semidet
source_open/5, % (+, +, @, @, -) is det
source_open/3, % (@, @, -) is det
source_close/1, % (+) is det
source_reset/1, % (+) is det
source_next/2, % (+, ?) is semidet
source_next_begin/1, % (+) is det
source_next_end/2 % (+, ?) is semidet
]).

:- module(nan_kernel_ex,
[ using_source/4, % (@, @, -, :) is nondet
using_sources/4, % (:, +, -, :) is nondet
source_first/2, % (+, ?) is semidet
source_enum/2, % (+, ?) is nondet
append_sources/2, % (+, -) is det
compose_sources/2 % (+, -) is det
]).
:- reexport('Nan.Kernel').

A quick example with the compose combinator showing the parallelism (and the
'using' constructs):

?- using_source(s1, sleep(2), _S1,
using_source(s2, sleep(2), _S2,
using_source(s3, sleep(2), _S3,
using_sources(compose_sources, [_S1, _S2, _S3], _S,
( time(source_next(_S, answer(_, the([A1, A2, A3]))))
))))).
% 546 inferences, 0.000 CPU in 2.000 seconds (0% CPU, Infinite Lips)
A1 = answer(last, the(s1)),
A2 = answer(last, the(s2)),
A3 = answer(last, the(s3)).

A preview of the code, with (few) more comments and examples, is on Gist
[**]. If the project confirms to be worth it, the idea is to go open on
GitHub under LGPL, as an SWI pack.

Feedback most welcome,

Julio

[*] Paul Tarau, "Fluents: A Refactoring of Prolog for Uniform Reflection and
Interoperation with External Objects":
<http://www.cse.unt.edu/~tarau/research/LeanProlog/RefactoringPrologWithFluents.pdf>

[**] A preview of the code is on Gist:
<https://gist.github.com/jp-diegidio/2914cac8b5cfb2b6a95e>


Markus Triska

unread,
Sep 3, 2015, 4:08:06 PM9/3/15
to
Hi Julio,

"Julio Di Egidio" <ju...@diegidio.name> writes:

> A preview of the code, with (few) more comments and examples, is on
> Gist [**]. If the project confirms to be worth it, the idea is to go
> open on GitHub under LGPL, as an SWI pack.
>
> Feedback most welcome,

Thank you for sharing this. It's always great when interesting code
snippets are shared here. I have a few comments regarding the code:

First, I find your uses of setup_call_cleanup/3 great! This is a very
nice and versatile predicate. Second, regarding naming: I suggest
(instead of the imperative "fail") to use "false" in analogy to "true".

The third suggestion also concerns the declarative aspects of the
program: You are using integer/1 at two places as a type test. However,
integer/1 is not a purely logical predicate, because it does not satisfy
basic algebraic laws like commutativity of conjunction. For example:

?- X = 1, integer(X).
X = 1.

versus:

?- integer(X), X = 1.
false.

Using must_be/2 ensures that your predicates remain declaratively sound:

?- X = 1, must_be(integer, X).
X = 1.

versus:

?- must_be(integer, X), X = 1.
ERROR: Arguments are not sufficiently instantiated

With this, Prolog tells you that the arguments are not sufficiently
instantiated to make a definite decision one way or the other at this
point. Also, must_be/2 yields a type error instead of failing silently
in cases like:

?- must_be(integer, a).
ERROR: Type error: `integer' expected, found `a' (an atom)

A more general and powerful way to handle such things are *constraints*.
In this case, CLP(FD) constraints are very useful to declaratively and
compactly express the intention, and they are available in many systems.

For example, instead of your predicate:

source_sid__num(type, Num) :-
integer(Num), Num >= 0, Num =< 1.

you can simply write, using CLP(FD) constraints:

source_sid__num(type, Num) :- Num in 0..1.

This gives you type checking automatically and works in all directions,
making your predicate both declaratively sound and more general.

All the best,
Markus

--
comp.lang.prolog FAQ: http://www.logic.at/prolog/faq/

Julio Di Egidio

unread,
Sep 3, 2015, 4:29:44 PM9/3/15
to
On Thursday, September 3, 2015 at 9:08:06 PM UTC+1, Markus Triska wrote:
> "Julio Di Egidio" <j***@diegidio.name> writes:
>
> > A preview of the code, with (few) more comments and examples, is on
> > Gist [**]. If the project confirms to be worth it, the idea is to go
> > open on GitHub under LGPL, as an SWI pack.
> >
> > Feedback most welcome,
>
> Thank you for sharing this. It's always great when interesting code
> snippets are shared here. I have a few comments regarding the code:

Thank you, you are welcome.

> First, I find your uses of setup_call_cleanup/3 great! This is a very
> nice and versatile predicate.

It is the only reliable way (that I know of) of managing allocation and cleanup of resources: we have threads, message_queues, and items in the recorded database.

> Second, regarding naming: I suggest
> (instead of the imperative "fail") to use "false" in analogy to "true".

I am using "fail" in the *operational* sense, and I am using "false" in the Boolean sense. My code is rather an example of keeping the two notions distinct and how that can be useful.

> The third suggestion also concerns the declarative aspects of the
> program: You are using integer/1 at two places as a type test.
>
> For example, instead of your predicate:
>
> source_sid__num(type, Num) :-
> integer(Num), Num >= 0, Num =< 1.
>
> you can simply write, using CLP(FD) constraints:
>
> source_sid__num(type, Num) :- Num in 0..1.

That is a nice catch and a nice tip, and there are indeed fixes possible above all around the "cross-cutting concerns", but there rather the point is that the whole conversion to numbers is useless in generating keys and shall just disappear.

Julio

Jan Burse

unread,
Sep 3, 2015, 7:17:45 PM9/3/15
to
Markus Triska schrieb:
> source_sid__num(type, Num) :-
> integer(Num), Num >= 0, Num =< 1.

The use of a must_be/2 predicate probably kills YAP Prolog.
There are Prolog systems such as YAP Prolog that detect
type checks after the head and include it in the indexing:

6.1 The Indexing Algorithm, Point 4 (Page 16)
http://arxiv.org/pdf/1102.3896.pdf

This is for example why YAP Prolog system is so bleeding
fast. But I am not sure whether YAP Prolog can also
detect \+ <type check>. Instead of must_be/2 I am
recently using another idiom:

source_sid__num(type, Num) :- \+ integer(Num), throw(...).
source_sid__num(type, Num) :- Num >= 0, Num =< 1.

Interestingly the \+ <type check> doesn't need a cut,
since it is followed by a throw, which will anyway remove
the choice points. But the idea of the idiom is of course
that the first clause should be read like it has a cut.

But the \+ <condition>, ! amounts to John McCarthys
abnormal, which has a couple of applications. I recently
experimented in two cases of using abnormal instead of
a custom flag/construction I had.

Results so far are that John McCarthys abnormal is
slower than my sys_nobarrier predicate property. In one
case, namely DCG transforms, John McCarthys abnormal
slowness was not important, since the DCG transform is
done at compile time. My version of the code roughly
uses something along:

dcg_body(NonTerminal, S0, S, Goal) :-
\+ dcg_constr(NonTerminal), !, ...

In another case John McCarthys abnormal was used
at runtime, and I saw a performance dip of ca. 10%
compared to the sys_nobarrier predicate property. I don't
know yet what to do about it. I was thinking about
a new construct \++ which can emit a cut:

:- set_predicate_property((\++)/2, sys_nobarrier).
\++(X) :- X, sys_local_cut, fail.
\++(_) :- !.

The DCG transform example would then be formulated
as follows, either explicitly by the end-user
or implicitly by the Prolog compiler which detects
the particular \+ <condition>, ! pattern:

dcg_body(NonTerminal, S0, S, Goal) :-
\++ dcg_constr(NonTerminal), ...

The SWI-Prolog parallel to the Jekejeke sys_nobarrier/0
flag and the Jekejeke sys_local_cut/1 predicate is
prolog_current_choice/1 and prolog_cut_to/1. Which
is used in Julios code (sic!). Here is SWI-Prolog
descriptions of prolog_cut_to/1, and it is used
in Julios source_exec__recv/4:

B.2 Ancestral cuts
http://www.swi-prolog.org/pldoc/doc_for?object=prolog_cut_to/1

Whereby SWI-Prolog has theoretically a greater application
are than my sys_nobarrier/0 and sys_local_cut/1, since
it can cut arbitrary ancestral level. But unfortunately
neither the SWI-Prolog predicates are in the ISO Standard
nor the Jekejeke features.

Thats why I was recently interested in John McCarthys
abnormal. Can Julios code be rewritten without this
SWI-Prolog specific ancestral cut, make it ISO
standard?

Bye

P.P.S.:
Open Article: John McCarthy's Legacy
http://www.sciencedirect.com/science/article/pii/S0004370210001827





Jan Burse

unread,
Sep 3, 2015, 7:57:47 PM9/3/15
to
Jan Burse schrieb:
> The use of a must_be/2 predicate probably kills YAP Prolog.

Except if in the case of SWI-Prolog or other Prolog systems,
the must_be/2 predicate is automatically expanded. Which
I doubt, since I don't find any inlining directive. It has
the following definition:

must_be(Type, X) :-
( has_type(Type, X)
-> true
; is_not(Type, X)
).

http://www.swi-prolog.org/pldoc/doc/swi/library/error.pl?show=src

So the cost it incures are two subgoals. The first subgoal
uses indexing on the first argument and could be easily inlined.
The second subgoal on the other hand is a little messier
and cannot easily be inlined. But lets give it a try. Assume
we have a goal:

must_be(integer, X)

This would give:

(integer(X) -> true;
var(X) -> throw(error(instantiation_error, _));
throw(error(type_error(integer, X)), _)))

Probably not anymore amenable to YAP JITing, but still
easy for many Prolog compilers, since the integer/1 and
var/1 ISO primitives can directly work on the Prolog
datastructure, for example if a tagged representation is
used, they are easy tag checks.

But totally unreadable for a manual inlining. So I
guess there is a benefit of must_be/2 for the programmer.
Imagine the above expansion for the following use case:

between(L, H, X) :-
must_be(integer, L),
must_be(integer, H),
...

But as long as the Prolog system does nothing about
it, the must_be/2 will slow down the code! Here is
the alternative idiom:

between(L, _, _) :- var(L),
throw(error(instantiation_error, _)).
between(L, _, _) :- \+ integer(L),
throw(error(type_error(integer, L)), _)).
between(_, H, _) :- var(H),
throw(error(instantiation_error, _)).
between(_, H, _) :- \+ integer(H),
throw(error(type_error(integer, H)), _)).
between(L, H, X) :- ...

Which is very YAP friendly I assume. I am currently
not 100% sure, I didn't yet verify whether it can also
handle \+ integer(_).

But the indexing can do much more. A YAP type like
indexing will elimininate certain clauses of between/3
from being tried at all, depending on the actual
type of the arguments.

But I guess we could go one step further, if we would
use call-site index caching. I didn't not yet implement
this kind of index in Jekejeke Prolog, and I don't know
whether some of the existing Prolog systems actually do
it. But the idea is simple, no further explanation here.

With call-site index caching we could totally eliminate
any checks for the types of between/3. For certain call-sites
a call to between/3 would directly go into the last clause.

So from a source code point of view must_be/2 is a good
idea. But it hinges upon its realization, to what optimizations
it is ammenable. So I am currently sticking to the other
idiom and trying to improve the indexing.

But the optimizations, which would also work for must_be/2
are probably only a matter of time, so it is expect that
must_be/2 could be the winner in the long run, and the
other idiom will go away.

Bye







Jan Burse

unread,
Sep 3, 2015, 9:14:00 PM9/3/15
to
Julio Di Egidio schrieb:
> - The overhead of threading being unnecessary for combinators, basic
> support for combinators is built in to the source object (via overloading);

Cool! Could try to roll something for Apache Camel:
http://camel.apache.org/enterprise-integration-patterns.html

If your Prolog system has a JVM integration I guess it
would be possible to use Prolog as a DSL to script the
Apache Camel stuff:

> To get started with Camel:
> 1) Create a CamelContext.
> 2) Optionally, configure components or endpoints.
> 3) Add whatever routing rules you wish using the DSL and RouteBuilder
or using Xml Configuration.
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> 4)Start the context.

Bye


Jan Burse

unread,
Sep 3, 2015, 9:21:37 PM9/3/15
to
In Apache Camel lingo: >>Fluent Builders<<

Jan Burse schrieb:

Jan Burse

unread,
Sep 3, 2015, 10:13:04 PM9/3/15
to
As a side note: The idea to allow multiple languages inside a
framework is also found in the Apache Spark Dataframes. But
this targets more big data and less enterprise integration.
But why not combine both?

Anyway, different language integration, basically an old
hat and a lot of headaches as well. I remember OMG. But
its coming up again and again since we need business
rules here and then, and people need a language to
write them.

So Apache Camel even claims to support PHP. I have seen
interactive server games written in PHP, like "Schattenwelt"
now defunct, was playing them for fun over a couple of
years before facebook had farmville integrated. But
I guess this is not what one has in mind when hearing PHP.

Anyway, current state of affairs, there is a JSR 223
and JSR 292, so there is API and better byte code to
integrate different languages into JVM. Oracle itself
delivers a JavaScript integration via nashorn.jar. So
when downloaded JDK 1.8, one can go on and run JavaScript
as follows:

% jjs
jjs> Math.sin(Math.PI/2)
1

The announced PHP integration for Apache Camel refers
to JSR 223 as well. But it guess it will probably not
use JSR 292, unless you have a very advanced jPHP.

http://camel.apache.org/php.html

Jan Burse schrieb:

Ulrich Neumerkel

unread,
Sep 5, 2015, 6:48:00 AM9/5/15
to
Markus Triska <tri...@logic.at> writes:
>Using must_be/2 ensures that your predicates remain declaratively sound:
>
> ?- X = 1, must_be(integer, X).
> X = 1.
>
>versus:
>
> ?- must_be(integer, X), X = 1.
> ERROR: Arguments are not sufficiently instantiated

This is a good case for using must_be/2. Unfortunately, must_be/2 in SWI
is itself not declaratively sound, as it provides some highly problematic
domains:

?- X = s(X), must_be(cyclic,X).
X = s(X).

?- must_be(cyclic,X).
ERROR: Domain error: `cyclic_term' expected, found `_G11118'

So a generalization of a success case leads to a domain error.
That's impossible.

Instead, use the more pedestrian itypes:

http://stackoverflow.com/a/30600104/772868

Julio Di Egidio

unread,
Sep 5, 2015, 9:07:56 AM9/5/15
to
On Friday, September 4, 2015 at 2:14:00 AM UTC+1, Jan Burse wrote:

> http://camel.apache.org/enterprise-integration-patterns.html
>
> I guess it would be possible to use Prolog as a DSL
> to script the Apache Camel stuff:

Well, it is the other way round actually: Prolog with Fluents is the implementation language on top of which one would build any patterns. IOW, the patterns are the DSL, Prolog with Fluents (then Interactors) is the implementation language. Tarau's paper(s) make that clear, indeed that is the whole point: e.g. "Arguably, fluents offer a more fexible management of input and output flows than the monolithical IO Monad. In fact, John Hughes recent proposal to replace monads with the more powerful concept of arrow with emphasis on directionality hints towards possible evolution towards a fuent-like concept."

That said, Fluents are not really enough, the next step is Interactors [1]. And we'd have an interesting question there:

All that is really needed to get from Fluents to Interactors is a 'return' operation, but how to handle that operation within our architecture?

Thank you,

Julio

[1] Paul Tarau1 and Arun Majumdar, "Interoperating Logic Engines":
<http://www.cse.unt.edu/~tarau/research/LeanProlog/InteroperatingLogicEngines.pdf>
<< We introduce a new programming language construct, Interactors, supporting the agent-oriented view that programming is a dialog between simple, self-contained, autonomous building blocks. We define Interactors as an abstraction of answer generation and refinement in Logic Engines resulting in expressive language extension and metaprogramming patterns. >>

Julio Di Egidio

unread,
Sep 5, 2015, 9:12:21 AM9/5/15
to
On Friday, September 4, 2015 at 12:17:45 AM UTC+1, Jan Burse wrote:

> Thats why I was recently interested in John McCarthys
> abnormal. Can Julios code be rewritten without this
> SWI-Prolog specific ancestral cut, make it ISO
> standard?

I will look into these abnormals, thanks for the reference. On the other hand consider that my code (the whole engine background loop) could simply be rewritten in terms of a state machine...

Julio

Jan Burse

unread,
Sep 5, 2015, 9:37:48 AM9/5/15
to
Julio Di Egidio schrieb:
>> >http://camel.apache.org/enterprise-integration-patterns.html
>> >
>> >I guess it would be possible to use Prolog as a DSL
>> >to script the Apache Camel stuff:
> Well, it is the other way round actually:

Well if you speculate on world domination through Prolog.
But then there is the Erlang, Scala, etc.. camp which
all also speculate on world domination.

He He, anyway, lets agree to disagree. I guess integration
would be better than domination. And this is one more
issue that is very much neglected by the ISO core standard:
- Foreign Function Interface (call-in and call-out)

For example Java, Fortran, Pascal, etc.. isn't agnostic
to this. And real Prolog systems aren't aswell agnostic
to this, lets look at SICStus, what concerns call-out
and even call-in, you have (sorry old release 3 docs):
Mixing C and Prolog
https://sicstus.sics.se/sicstus/docs/3.7.1/html/sicstus_11.html

Mixing Java and Prolog
https://sicstus.sics.se/sicstus/docs/3.7.1/html/sicstus_12.html

So we have two neglected issues by the ISO core standard,
multi-threading and foreign function interface, and of
course all questions about the combination of both.

Nevertheless we hear "industry strength" here and then.
A standard is not industry strength if it doesn't cover
multi-threading and foreign function interface.

There might be Prolog systems that are industry used,
but not because of the ISO core standard, its more
an academic toy, than an industry strength standard.

Bye

Julio Di Egidio

unread,
Sep 5, 2015, 10:07:13 AM9/5/15
to
On Saturday, September 5, 2015 at 2:37:48 PM UTC+1, Jan Burse wrote:
> Julio Di Egidio schrieb:
> >> >http://camel.apache.org/enterprise-integration-patterns.html
> >> >
> >> >I guess it would be possible to use Prolog as a DSL
> >> >to script the Apache Camel stuff:
> > Well, it is the other way round actually:
>
> Well if you speculate on world domination through Prolog.
> But then there is the Erlang, Scala, etc.. camp which
> all also speculate on world domination.

I am actually interested in "programming in logic", ultimately in computability logic: it is runnable specifications on a side, on the other side it has the power to build all other paradigms on top of it. Namely, I would indeed contend that "programming in logic" is the most fundamental programming paradigm!

But Prolog is already way underrated and quite erroneously considered a high level language: it isn't, it is the opposite of it. (In fact, I'd rather be interested in building a compatibility layer for at least SWI and Jekejeke for this library of Interactors, there are already applications for embedded systems, for example.

Incidentally, I do concur that the current Prolog standard is incomplete and broken, plus, what's really the showstopper, a closed academic game. It is time maybe to rewrite a new language from scratch, one where not only the paradigm is reviewed and consolidated (and we also get rid of all the unneeded extra-complications), but also one where engineering concerns are not simply banned but rather embraced as the real driving factor.

My 2c...

Julio

Jan Burse

unread,
Sep 5, 2015, 10:14:32 AM9/5/15
to
ulr...@mips.complang.tuwien.ac.at (Ulrich Neumerkel) schrieb:
> Instead, use the more pedestrian itypes:
>
> http://stackoverflow.com/a/30600104/772868

Looks rather a joke to me. You are using functor/3
to force an instantiation error. Admitting that the
ISO core standard has a further issue?

What could this further issue be? Well the issue
is I guess, that the ISO core standard defines
a throw/1 predicate. But nobody knows how to
correctly use the throw/1 predicate.

It is not clear that the error class term
must be put into a further error/2 term. And it is
not clear when and how the second argument of error/2
is filled with a stack trace.

If all this were clear you would simply define
as follows, assuming throw/2 fills the stack
trace in the second argument, only then it
does the same as functor/3:

atom_itype(A) :- var(A), throw(error(instantiation_error,_)).
atom_itype(A) :- atom(A).

Although elegant on first sight, I don't think
using functor/3 is a good programming practice.
Just think about it. functor/3 has a main
use case scenario and alternative use case
scenarios.

The main use case scenario of functor/3 is
to provide functor atomic and arity integer
and vice versa. Throwing errors is an alternative
path in the code. And we know all that this
alternative path is not the same for all Prolog
systems.

So youre functor(A, _, _) might equally well
throw an integer type error or atomic type
error on some Prolog system. You never know.
An explicit throw/1 looks much better to me,
if only it would work for all Prolog systems.

For more incompatibilities besides filling
the context see below. A further incompatibility
is in the error class term. You don't know
whether you need to throw instantiation_error/0
or instantiation_error/2.

Bye

P.S.: The ISO core standard says the Context
argument in error(Formal, Context) is implementation
dependent. This is fine, but refers to the format
of the Context. And the hidden assumption is that,
the builtins use this format and fill the Context.

But what about a user issued throw/2 error?
If I remember well this is not covered
by the ISO core standard. The SWI-Prolog
with a special hook is not the worst:
http://www.swi-prolog.org/pldoc/man?predicate=prolog_exception_hook/4

An other approach to assure filling would
be to provide a separate predicate that does
just this. The take of SICStus Prolog is
illarg/[3,4], which takes its own error
class term which is again mapped to a differnt
non ISO conformat error class term:
https://sicstus.sics.se/sicstus/docs/4.0.0/html/sicstus/lib_002dtypes.html#lib_002dtypes

In the above reference we find even a must_be/4,
the bigger brother of must_be/1. My own take
is to stick to the ISO error class terms,
and provide a predicate sys_throw_error/1.
So the above code would be written:

atom_itype(A) :- var(A), sys_throw_error(instantiation_error).
atom_itype(A) :- atom(A).

The Jekejeke infrastructure(*) is such that
non ISO conformant error class terms can
be totally avoided in that we allow putting
additonal information into the context that
not only consists of a backtrace.

So when SICStus wants to do:

error(instantion_error(Goal, Index), Context)

We can also do it in Jekejeke as:

error(instantion_error, [arg(Goal, Index)|Context]).

(*)
See the fetchStack, fetchLocation and fetchPos builder:
http://www.jekejeke.ch/idatab/doclet/prod/docs/05_run/10_docu/03_interface/07_call/05_exception.html
These builder apply to the context, and can be used
before construction the exception.

Jan Burse

unread,
Sep 5, 2015, 10:28:07 AM9/5/15
to
Julio Di Egidio schrieb:
> I am actually interested in "programming in logic",
> ultimately in computability logic: it is runnable
> specifications on a side, on the other side it has
> the power to build all other paradigms on top of it.
> Namely, I would indeed contend that "programming in
> logic" is the most fundamental programming paradigm!

Yes, I understand. There are other paradigms that try
the same. For example ML, functional programming paradigm,
is used to bootstrap a lot of Isabelle/HOL.

But then peng, Isabelle/HOL runs inside jEdit which
is written in Java. There is a certain legibility of
doing this. jEdit only provides the editing of some
"text", and its still the ML and Isabelle/HOL engine
doing the verification.

Similar integration is possible with Prolog. Take
for example the use of XPCE in SWI-Prolog. XPCE is
not written in Prolog.
http://www.swi-prolog.org/packages/xpce/

Julio Di Egidio

unread,
Sep 5, 2015, 11:02:10 AM9/5/15
to
On Saturday, September 5, 2015 at 2:37:48 PM UTC+1, Jan Burse wrote:
> Julio Di Egidio schrieb:
> >> >http://camel.apache.org/enterprise-integration-patterns.html
> >> >
> >> >I guess it would be possible to use Prolog as a DSL
> >> >to script the Apache Camel stuff:
> > Well, it is the other way round actually:
>
> Well if you speculate on world domination through Prolog.
> But then there is the Erlang, Scala, etc.. camp which
> all also speculate on world domination.
>
> He He, anyway, lets agree to disagree. I guess integration
> would be better than domination.

But I am talking of underlying programming paradigms, not just of language implementations and technical factors in general, such as integration (which I too advocate).

The key idea being that "programming in logic" (with interactors or similar) is the next generation of... an *assembler* language! On top of which of course one can have whatever one likes.

And the critical issue I think is around the *operational* semantics of Prolog: I would go as far as to propose that there should be *only* an operational semantics, and that e.g. emphasis on pure Prolog is misplaced as *cuts* rather make deterministic what deterministic otherwise cannot be, and so on... IOW, I'd say the primacy of declarative semantics (eventually, its very existence) is the showstopper there.

Julio

Julio Di Egidio

unread,
Sep 5, 2015, 11:31:09 AM9/5/15
to
On Thursday, September 3, 2015 at 3:09:47 AM UTC+1, Julio Di Egidio wrote:

> [*] Paul Tarau, "Fluents: A Refactoring of Prolog for Uniform Reflection and
> Interoperation with External Objects":
> <http://www.cse.unt.edu/~tarau/research/LeanProlog/RefactoringPrologWithFluents.pdf>
>
> [**] A preview of the code is on Gist:
> <https://gist.github.com/jp-diegidio/2914cac8b5cfb2b6a95e>

Fluents are not really enough, the next step is Interactors [1], and I'd have a basic question there:

All that is really needed to get from Fluents to Interactors is a 'return' operation (indeed Tarau mentions it once already in his paper on Fluents, to implement throw/1, but does not define it), but:

How to handle the 'return' operation within our architecture?

(Our engines execute arbitrary Prolog goals and the only way to implement a 'return' operation, it seems to me, is by throwing some specific error that the engine loop would catch. But then it is not clear to me what resuming an execution would mean...)

Julio Di Egidio

unread,
Sep 5, 2015, 11:46:51 AM9/5/15
to
On Saturday, September 5, 2015 at 4:31:09 PM UTC+1, Julio Di Egidio wrote:

> (Our engines execute arbitrary Prolog goals and the only way to implement a 'return' operation, it seems to me, is by throwing some specific error that the engine loop would catch. But then it is not clear to me what resuming an execution would mean...)

Well, I am already having a hunch that I may be just taking that from the wrong side... Let's think about it.

Cheers,

Julio

Jan Burse

unread,
Sep 5, 2015, 12:33:12 PM9/5/15
to
Hi,

What do you mean by return? In Erlang, if an Erlang process
terminates its derivation, it will also terminate as a "thread".
So if you have (pseudo Prolog, ? means receive):

listener(Channel) :-
Channel ? Event,
<Do Something>,
listener(Channel).

Then the above loops for ever and processes the events. But
one can also do the following:

listener(Channel) :-
Channel ? Event,
handle(Event, Channel).

handle(stop, _) :- !.
handle(Event, Channel) :-
<Do Something>,
listener(Channel).

If you do the second code, a stop event will stop the
listener from further processing.

Most of the challenges to do such stuff is to allow the
end-user to exactly code in the above style and releave
the burder from the end-user in calling deallocates for
the involved threads and channels.

But for example the underscore _ in the first handle/2
clause, which should somehow release the channel,
can be also handled by the GC. In Java one could even
implement a finalize() method if external resources are
involved.

For internal channels, that don't make use of external
resources, such as a simple memory queue, a finalize()
method is even not needed. Just leave it to the GC
if you can manage that no threads are inside a monitor
and waiting.

But if the thread who sent the stop has already finished
its sending, he is sooner or later outside of the
queue monitor, so that no more stack frame point to
the queue and well the GC will remove it.

Bye

Julio Di Egidio schrieb:

Jan Burse

unread,
Sep 5, 2015, 12:37:51 PM9/5/15
to
Jan Burse schrieb:
> But if the thread who sent the stop has already finished
> its sending, he is sooner or later outside of the
> queue monitor, so that no more stack frame point to
> the queue and well the GC will remove it.

Disclaimer, speculations, speculations, ... Everything
could be much more complicated in practice, or even
simpler.

Julio Di Egidio

unread,
Sep 5, 2015, 1:17:11 PM9/5/15
to
On Saturday, September 5, 2015 at 5:33:12 PM UTC+1, Jan Burse wrote:

> Hi,
>
> What do you mean by return?

Read the papers: understanding what return really means was my question... :)

Julio

Jan Burse

unread,
Sep 5, 2015, 5:29:13 PM9/5/15
to
The paper says:

> We have chosen this implementation scenario in our Kernel
> Prolog compiler which provides a return/1 operation to exit
> an engine's emulator loop with an arbitrary answer pattern,
> possibly before the end of a successful derivation.

Its only used in the kernel prolog specific implementation
of throw/1. You could use the ISO throw/1 directly. Its not
meant to be part of the fluent interface. This is my guess
here.

BTW: I wonder how you simulate the trailing of fluents.
setup_call_cleanup/3 doesn't provide trailing. Trailing
means that a fluent should survive a cut.

That we have also here a gap in the ISO core standard,
was recently also noticed by Paulo Moura, he tweeted:

"Prolog lacks a logical/standard solution to handle
global backtrackable state changes, pushing users
to use nasty hacks or to highjack DCGs."
https://twitter.com/LogtalkDotOrg/status/627105057289453568

I can only agree, provided Paulo Moura means the same
as I have in mind. And I guess he is refering to another
paper by Paul Tarau which shows trailing via DCGs. But
I might be wrong.

Paul Tarau in the present paper seems to have an API
for trailing which consist simply of a getTrail() method
and then a push() method. I could be also wrong here,
that it is a cut trailing and not a variable trailing
as I am assuming.

In Jekejeke Prolog I have a similar mechanism, not as
an API on the Java level, but as a predicate on
the Prolog level.

sys_unbind(A):
The predicate installs an unbind handler A and immediately
succeeds. The unbind handler is invoked during a redo or a close.
http://www.jekejeke.ch/idatab/doclet/prod/docs/15_min/10_docu/02_reference/07_theory/05_system/04_trail.html

So you would create a thread based Tarau fluent as
follows in Jekejeke Prolog (using a yet unpublish
thread library and queuing library):

start_fluent(Answer, Goal, Control, Result) :-
sys_atomic((thread_create(
enum_fluent(Answer, Goal, Control, Result)),
sys_undo(Control ! stop))).

enum_fluent(Answer, Goal, Control, Result) :-
Control ? Command,
(Command == stop -> !; fail),
(Goal,
Result ! the(Answer),
Control ? Command,
(Command == stop -> !; fail); Result ! no).

next_fluent(Control, Result, Answer) :-
Control ! next,
Result ? Answer.

stop_fluent(Control) :-
Control ! stop.

But the name fluent for the above thing is kind of
an abuse, if it is implemented without a thread. Then
its just an iterator. With threads, its a little bit
more but no so much more.

The more general model would be to just allow
threads to use (?)/2 (receive) and (!)/2 (send) as
they wish. The Tarau "fluent" is then an instance of
a different problem, namely how to return a collection
of results on a single request.

Also it begs a little bit the question whether we
should always stop a thread during undo, and not
also have scenarios where a thread should live
longer than its creation point.

The wish for sys_undo/1, respectively my wish for
a sys_undo/1 standardization rather stems from
constraint programming, where we want to clean-up
constraints during backtracking.

But the constraint clean-up should not be induced
by a cut. We all assume that this does not happen,
for example in SWI-Prolog, constraints survive a
cut, but not a redo:

Welcome to SWI-Prolog (Multi-threaded, 64 bits, Version 7.3.6)
Copyright (c) 1990-2015 University of Amsterdam, VU Amsterdam

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

?- X #< 10.
X in inf..9.

?- X #< 10, !.
X in inf..9.

?- X #< 10; X #>= 10.
X in inf..9 ;
X in 10..sup.

Bye

P.S.:
sys_undo/1 is borrowed/inspired from SICStus undo/1.

P.P.S.:
Mercury has a very elaborate trailing API that
can do a little bit more than getTrail() and push().

Julio Di Egidio schrieb:

Jan Burse

unread,
Sep 5, 2015, 5:37:12 PM9/5/15
to
Jan Burse schrieb:
> Its only used in the kernel prolog specific implementation
> of throw/1. You could use the ISO throw/1 directly. Its not
> meant to be part of the fluent interface. This is my guess
> here.

What would be extremly interesting would be if kernel
prolog or another Prolog system would implement
a transfer/2.

PROCEDURE TRANSFER (VAR from: COROUTINE; to: COROUTINE);
(* Returns the identity of the calling coroutine in from, and
transfers control to
the coroutine specified by to.
*)
http://www.modula2.org/reference/isomodules/isomodule.php?file=COROUTIN.DEF

You could call transfer/2 and jump from one fluent
to another fluent, without the need for threads.

The type COROUTINE is just a frozen state of a
normal ROUTINE, but not that frozen as a parked
thread.

Translated to Prolog it would be just an engine
which is executed, and possibly temporarily halted
at some point.


Bye

Jan Burse

unread,
Sep 5, 2015, 5:40:57 PM9/5/15
to
Jan Burse schrieb:
> BTW: I wonder how you simulate the trailing of fluents.
> setup_call_cleanup/3 doesn't provide trailing. Trailing
> means that a fluent should survive a cut.

I guess the trailing is one more instance of:

Jan Burse schrieb:

Jan Burse

unread,
Sep 6, 2015, 6:02:24 AM9/6/15
to
Jan Burse schrieb:
>
> So youre functor(A, _, _) might equally well
> throw an integer type error or atomic type
> error on some Prolog system. You never know.
> An explicit throw/1 looks much better to me,
> if only it would work for all Prolog systems.

For example:

In Ciao Prolog functor(,,_) silently fails.

Jan Burse

unread,
Sep 6, 2015, 6:03:05 AM9/6/15
to
Jan Burse schrieb:
>
> In Ciao Prolog functor(,,_) silently fails.

Corr.: In Ciao Prolog functor(_,_,_) silently fails.

Ulrich Neumerkel

unread,
Sep 6, 2015, 6:39:30 AM9/6/15
to
Jan Burse <janb...@fastmail.fm> writes:
>ulr...@mips.complang.tuwien.ac.at (Ulrich Neumerkel) schrieb:
>> Instead, use the more pedestrian itypes:
>>
>> http://stackoverflow.com/a/30600104/772868
>
>Looks rather a joke to me. You are using functor/3
>to force an instantiation error. Admitting that the
>ISO core standard has a further issue?
>
>What could this further issue be? Well the issue
>is I guess, that the ISO core standard defines
>a throw/1 predicate. But nobody knows how to
>correctly use the throw/1 predicate.
>
>It is not clear that the error class term
>must be put into a further error/2 term. And it is
>not clear when and how the second argument of error/2
>is filled with a stack trace.

The second argument of error/2 is Implementation defined. So
it is up to an implementation to use it properly and define that.
That is, if you put whatever into the second argument you will
most likely collide with the definition of a concrete implementation.
For this reason it makes sense to write functor(I, _, _) instead.

For some time, you got instantiation errors in SICStus Prolog,
when the second argument was _. This has changed recently
to a slightly more user friendly action.

The idea to use the second argument to effectively produce (part of)
a stack trace sounds very interesting. I have not seen it,
though. Please also take into account the approach by IF/Prolog:
There the second argument is a list of (=)/2-pairs to indicate
all kinds of useful information. For example, for instantiation
errors for arithmetical expressions, it also gives:

valid_type = evaluable
goal = ...

which is quite helpful information. It goes even a bit further:
erroneous goals may be replaced by other goals.


Jan Burse

unread,
Sep 6, 2015, 6:59:32 AM9/6/15
to
ulr...@mips.complang.tuwien.ac.at (Ulrich Neumerkel) schrieb:
> Please also take into account the approach by IF/Prolog:
> There the second argument is a list of (=)/2-pairs to indicate
> all kinds of useful information. For example, for instantiation
> errors for arithmetical expressions, it also gives:
>
> valid_type = evaluable
> goal = ...
>
> which is quite helpful information. It goes even a bit further:
> erroneous goals may be replaced by other goals.

Interesting.

IF/Prolog is very difficult to access and assess. Still
didn't figure out how to get hold of an evaluation copy.

Bye

Jan Burse

unread,
Sep 6, 2015, 7:05:58 AM9/6/15
to
The SETUP.EXE doesn't execute on 64-bit machine.
Even when setting it to 32-bit compatibility.

Jan Burse schrieb:

Jan Burse

unread,
Sep 6, 2015, 7:17:13 AM9/6/15
to
Hi,

> So youre functor(A, _, _) might equally well
> throw an integer type error or atomic type
> error on some Prolog system. You never know.
> An explicit throw/1 looks much better to me,
> if only it would work for all Prolog systems.

SICStus 4.3.2 (x86_64-win32-nt-4): Sat May 9 15:07:51 WEDT 2015

| ?- functor(_,_,_).
! Instantiation error in argument 3 of functor/3
! goal: functor(_4631,_4633,_4635)

But I guess your intention is the first argument.

Ulrich Neumerkel

unread,
Sep 6, 2015, 2:05:38 PM9/6/15
to
I answered that on SO already. It's a little tiresome to
write in two places simultaneously.

Jan Burse

unread,
Sep 6, 2015, 3:43:17 PM9/6/15
to
Hi,

Its more annoying when somebody doesn't understand:

"You don't understand. I was refering to the error message in the
top-level and not to the error class term. The error message is of
interest to end-users. Thats what they see first before they wrap their
top-level query into a catch. And I doubt that they only look at the
first argument of error/2."

Bye

ulr...@mips.complang.tuwien.ac.at (Ulrich Neumerkel) schrieb:

Julio Di Egidio

unread,
Sep 11, 2015, 9:57:04 AM9/11/15
to
On Saturday, September 5, 2015 at 5:33:12 PM UTC+1, Jan Burse wrote:

> What do you mean by return? In Erlang, if an Erlang process
> terminates its derivation, it will also terminate as a "thread".

It is not it, and the two Tarau's papers I have linked do explain it, the second paper on interactors in particular is where you find a definition of return and examples: a return operation (in Tarau's terminology) is in fact the key to extend fluents to interactors. OTOH, return already appears, but not defined, in the first paper on fluents, where it is needed to show that these primitives can recover full ISO prolog, which is to begin with used as an example of their power. Indeed Tarau goes as far at some point as to propose that interactors be used to rewrite a runnable ISO standard specification of Prolog, an enriched one with his combinators (return itself is a meta-predicate).

The difference with what you mention above is that this return do suspends the computation, the goal does not have to complete. Then coding lazy patterns becomes a joke, and so on. Please read the papers, the second one for return... :)

Julio

Julio Di Egidio

unread,
Sep 11, 2015, 10:16:56 AM9/11/15
to
Return is expected to suspend the computation of a given goal (in the context of the worker thread that is executing the goal) without disrupting the backtracking: we must also be able to resume the computation at any time.

In Tarau, fluents then interactors are built on top of a Horn Clause interpreter, so there is an interpreter one can tweak. In my approach with threads and arbitrary Prolog goals, there are just the built-in interpreter and backtracking of the hosting Prolog system (SWI here), so, to begin with, suspending a Prolog goal at an arbitrary point in its execution is simply not doable unless maybe with low level hacks such as blocking messages and thread implicit queues (which do not require a handle to the parent...).

In the meantime I am also thinking that mine might be a pointless enterprise. As Tarau puts it, in his approach we have the benefit of keeping backtracking and threading as independent issues, with all the advantages, including the ability to implement a return that lets the user return an arbitrary answer at an arbitrary point of any computation, and suspends the computation until closing or resuming. But that also means that we are rather writing a system from scratch, which would certainly outperform any implementation on top of a pre-existing Prolog system.

Julio

Julio Di Egidio

unread,
Sep 11, 2015, 12:10:05 PM9/11/15
to
Although, considering that a predicate containing a return call is itself a meta-predicate, then indeed we might be able to implement return with no hacks...

I need to think more about it.

Julio

Jan Burse

unread,
Sep 11, 2015, 10:19:45 PM9/11/15
to
Hi,

The CLU Language by Barabara Liskov had
iterors. She said, well a function looks
as follows:

proc ... return ...

Why not have also iterators:

iter ... yield ...

Some of Taraus stuff are just iterators.
The return statement, is it a yield or
a return statement?

Bye

See also fig 5 here:
https://www.cs.virginia.edu/~weimer/615/reading/liskov-clu-abstraction.pdf

P.S.: In Prolog I would define
a yield operator as follows:

yield(P,R,C) :- R = P; C.

C is the subsequent code in the body of
the prediate, R is the result that should
be yielded and P is the result parameter
variable of the predicate.

So basically Prolog choice points
implement iterators. Here is an example:

p(X) :- yield(X,1,yield(X,2,yield(X,3,fail))).

?- p(X).

Prolog just doesn't need the for statement
of CLU to invoke an iterator. Just place
a query, and it works. What tarau does, it
makes the iterator explicit by the Fluent
interface.

But using the name Fluent is a little over-
selling I guess. More modest names are
seen here:

http://docs.oracle.com/javase/7/docs/api/java/util/Enumeration.html

http://docs.oracle.com/javase/7/docs/api/java/util/Iterator.html

But the above interfaces lack a end-of-lifecycle
method for the iterator. The above interfaces
work for iterator objects that are automatically
reclaimed by GC.

So a Fluent has a stop() to control the lifecycle
of the iterator. This can be seen in many places,
this extension to iterators. For example an SQL
cursor can be closed. Etc..


Julio Di Egidio schrieb:

Jan Burse

unread,
Sep 11, 2015, 10:20:42 PM9/11/15
to
Jan Burse schrieb:
>
> p(X) :- yield(X,1,yield(X,2,yield(X,3,fail))).
>
> ?- p(X).

Welcome to SWI-Prolog (Multi-threaded, 64 bits, Version 7.3.6)
Copyright (c) 1990-2015 University of Amsterdam, VU Amsterdam
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software,
and you are welcome to redistribute it under certain conditions.
Please visit http://www.swi-prolog.org for details.

For help, use ?- help(Topic). or ?- apropos(Word).

1 ?- [user].
yield(P,R,C) :- R=P; C.
|:
true.

2 ?- [user].
p(X) :- yield(X,1,yield(X,2,yield(X,3,fail))).
|:
true.

3 ?- p(X).
X = 1 ;
X = 2 ;
X = 3 ;
false.

4 ?-

Jan Burse

unread,
Sep 11, 2015, 10:37:47 PM9/11/15
to
Hi,

It seems that even CLU at MIT in the 80's
was not the first languag with iterators,
this paper mentions Alphard at CMU in the
70's. See here:

Iterators revisited: proof rules and implementation
http://research.microsoft.com/en-us/projects/specsharp/iterators.pdf

Anyway, nested iterators, piece of cake
for Prolog code, right?

Bye

Jan Burse schrieb:

Julio Di Egidio

unread,
Sep 12, 2015, 8:38:49 AM9/12/15
to
On Saturday, September 12, 2015 at 3:19:45 AM UTC+1, Jan Burse wrote:

> Some of Taraus stuff are just iterators.

You just keep missing the whole point: Tarau, with pure horn clauses plus three basic combinators, gives you such a powerful logical "assembler" language as to be able to recover full ISO Prolog, or functional patterns, or imperative, or literally what have you.

> The return statement, is it a yield or a return statement?

I don't know why Tarau decided to call it with a possibly ambiguous "return", it is definitely a yield, as clearly explained since the introductions of both papers.

> P.S.: In Prolog I would define a yield operator as follows:
>
> yield(P,R,C) :- R = P; C.

Nope, there you need to backtrack to an alternative branch and lose previous bindings. That is just not it.

Read the bloody papers if you want to start contributing: in the meantime, EOD.

Julio

Julio Di Egidio

unread,
Sep 12, 2015, 9:01:04 AM9/12/15
to
On Saturday, September 12, 2015 at 1:38:49 PM UTC+1, Julio Di Egidio wrote:
> On Saturday, September 12, 2015 at 3:19:45 AM UTC+1, Jan Burse wrote:
>
> > Some of Taraus stuff are just iterators.
>
> You just keep missing the whole point: Tarau, with pure horn clauses plus three basic combinators, gives you such a powerful logical "assembler" language as to be able to recover full ISO Prolog, or functional patterns, or imperative, or literally what have you.
>
> > The return statement, is it a yield or a return statement?
>
> I don't know why Tarau decided to call it with a possibly ambiguous "return", it is definitely a yield, as clearly explained since the introductions of both papers.

Return is defined in section "3.1 A yield/return operation" of the paper on Interactors (linked up-thread).

> > P.S.: In Prolog I would define a yield operator as follows:
> >
> > yield(P,R,C) :- R = P; C.
>
> Nope, there you need to backtrack to an alternative branch and lose previous bindings. That is just not it.

I take that back, I still need to think about it...

Let's consider this concrete example, given in section "7.2 Encapsulating Infinite Computations Streams" of the same paper:

"An infinite stream of natural numbers is implemented as:

loop(N) :- return(N), N1 is N+1, loop(N1)."

I suppose a return defined along the lines of yours would allow one to write:

loop(N) :- return(N, (N1 is N+1, loop(N1)).

But I am not sure that really cuts it (plus some hack in my implementation would still be needed: there is not anymore the problem of suspending the computation, but there still is the problem of not having a handle to send back answers to).

Julio

Julio Di Egidio

unread,
Sep 12, 2015, 9:54:44 AM9/12/15
to
On Saturday, September 12, 2015 at 2:01:04 PM UTC+1, Julio Di Egidio wrote:
> On Saturday, September 12, 2015 at 1:38:49 PM UTC+1, Julio Di Egidio wrote:
> > On Saturday, September 12, 2015 at 3:19:45 AM UTC+1, Jan Burse wrote:
<snip>
> > > P.S.: In Prolog I would define a yield operator as follows:
> > >
> > > yield(P,R,C) :- R = P; C.
> >
> > Nope, there you need to backtrack to an alternative branch and lose previous bindings. That is just not it.
>
> I take that back, I still need to think about it...
>
> Let's consider this concrete example, given in section "7.2 Encapsulating Infinite Computations Streams" of the same paper:
>
> "An infinite stream of natural numbers is implemented as:
>
> loop(N) :- return(N), N1 is N+1, loop(N1)."
>
> I suppose a return defined along the lines of yours would allow one to write:
>
> loop(N) :- return(N, (N1 is N+1, loop(N1)).
>
> But I am not sure that really cuts it (plus some hack in my implementation would still be needed: there is not anymore the problem of suspending the computation, but there still is the problem of not having a handle to send back answers to).

Not even that problem, as here the goal completes and binds variables. Indeed, it is a bit clumsy, but otherwise maybe it is a solution.

Here is what I mean by clumsy, take another of Tarau's examples:

"throw(E) :- return(exception(E))."

I am not puzzled by how to rewrite that in our terms, the engine would simply ignore any continuation, so we could just rewrite:

throw(E) :- return(exception(E), fail). % or whichever Cont

But I am trying to think the more general case and detection of determinism.

Consider this (where 'if' is a combinator if(Cond,Then,Else), easily definable from our primitives): to get a loop(N,Max) predicate that is also sensitive to determinism, we would end up writing:

loop(N,Max) :-
if(
N=:=Max,
return(N, fail),
if(
N<Max,
return(N, (N1 is N+1, loop(N1,Max)),
return(fail, fail) % or whichever Cont
)
).

Where the literal 'fail' as a continuation in return could be the signal to the engine that this is the last solution.

For comparison, in Tarau's, we would just write:

loop(N,Max) :- N=<Max, return(N, (N1 is N+1, loop(N1,Max)).

But I suppose we can live with some more complex construction than in Tarau's (and the above can also be helped a little bit with a return/1, of course), considering also that in Tarau's design there just is no determinism detection and I wouldn't see any easy way to implement it on top of his primitives...

So, would that do?

Julio

Julio Di Egidio

unread,
Sep 12, 2015, 10:08:21 AM9/12/15
to
No, that is what we could write with our return if we did not care for determinism detection. Is there a negative impact on compilation of clauses by passing a continuation? Otherwise, at first sight at least, it is looking good enough to me...

(And I'll pause for now.)

Julio

Julio Di Egidio

unread,
Sep 12, 2015, 10:26:17 AM9/12/15
to
On Saturday, September 12, 2015 at 3:08:21 PM UTC+1, Julio Di Egidio wrote:

> > loop(N,Max) :- N=<Max, return(N, (N1 is N+1, loop(N1,Max)).
>
> No, that is what we could write with our return if we did not care for determinism detection. Is there a negative impact on compilation of clauses by passing a continuation? Otherwise, at first sight at least, it is looking good enough to me...
>
> (And I'll pause for now.)

Sorry, but no, it is just not that simple. Consider again throw/1:

"throw(E) :- return(exception(E))."

It is not binding variables...

Julio

j4n bur53

unread,
Sep 12, 2015, 1:37:28 PM9/12/15
to
Hi,

Here is the yield/return programming challenge.
Take as a starting point the following code,
a little interpreter for an imperative language
written in Prolog:

An Embedded ALGOL-like language in Prolog

http://muaddibspace.blogspot.ch/2008/03/embedded-algol-like-language-in-prolog.html

The above little interpreter has already a return,
whereby I am not claiming it is the same return as
Tauraus return.

Exercise:
How would you code a yield statement
for the above little interpreter
in Prolog?

Bye


Julio Di Egidio schrieb:

Jan Burse

unread,
Sep 12, 2015, 1:43:35 PM9/12/15
to
Hi,

Corr.:

Exercise I:
How would you correct the little interpreter
so that it handles returns correctly, i.e.
doesn't run past returns.(*)

Exercise II:
How would you then code a yield statement
for the above little interpreter
in Prolog?

Bye

(*)
The problem is the following rule:

run((First; Second), EnvI, O, Ret) :-
run(First, EnvI, M, _), run(Second, M, O, Ret).

We the above definition of (;)/2 the result of the
following code:

return a;
return b

will be b instead of a.

j4n bur53 schrieb:

Julio Di Egidio

unread,
Sep 13, 2015, 7:06:30 AM9/13/15
to
On Saturday, September 12, 2015 at 6:37:28 PM UTC+1, j4n bur53 wrote:

> http://muaddibspace.blogspot.ch/2008/03/embedded-algol-like-language-in-prolog.html
>
> The above little interpreter has already a return,
> whereby I am not claiming it is the same return as
> Tauraus return.

It isn't: indeed, it isn't any nearer to our needs than your previous attempts were, and for the same reasons.

Julio

Julio Di Egidio

unread,
Sep 13, 2015, 8:23:31 AM9/13/15
to
On Saturday, September 12, 2015 at 3:08:21 PM UTC+1, Julio Di Egidio wrote:
> On Saturday, September 12, 2015 at 2:54:44 PM UTC+1, Julio Di Egidio wrote:
> > On Saturday, September 12, 2015 at 2:01:04 PM UTC+1, Julio Di Egidio wrote:
> > > On Saturday, September 12, 2015 at 1:38:49 PM UTC+1, Julio Di Egidio wrote:
> > > > On Saturday, September 12, 2015 at 3:19:45 AM UTC+1, Jan Burse wrote:
> > > <snip>
> > > > > P.S.: In Prolog I would define a yield operator as follows:
> > > > >
> > > > > yield(P,R,C) :- R = P; C.
<snip>
> > > I suppose a return defined along the lines of yours would allow one to write:
> > >
> > > loop(N) :- return(N, (N1 is N+1, loop(N1)).
> > >
> > > But I am not sure that really cuts it (plus some hack in my implementation would still be needed: there is not anymore the problem of suspending the computation, but there still is the problem of not having a handle to send back answers to).
<snip>
> > Here is what I mean by clumsy, take another of Tarau's examples:
> >
> > "throw(E) :- return(exception(E))."

Return is defined as returning arbitrary *answers*. Unless I am missing something, a problem with Tarau's presentation is that he should rather be writing:

loop(N) :- return(the(N)), N1 is N+1, loop(N1).

Then, as an example of its use, one would write:

above(N0, N) :-
using_source(N, loop(N0), S,
source_enum(S, the(N))
).

(Our answer term is slightly more complex, but the idea is the same.)

With our approach, where an answer source runs the given goal in a worker thread and there is no control on the interpreter, I am pretty convinced we cannot but rewrite the above (along the lines of your suggestion) as:

loop(N) :- return(the(N)); N1 is N+1, loop(N1).

because we simply have no way to suspend/resume the underlying interpreter. Then our return really boils down to just returning arbitrary answers at arbitrary points in the computation, but cannot alter the flow of the computation itself (I mean, not even with the hacks: it is plain impossible). But then the semantics of our return becomes a bit vague:

When the given goal terminates, the worker loop would usually just propagate the bindings. If one or more returns were issued before the goal came to termination, it is not clear what the worker should do: return, in sequence, all solutions *plus* the final binding or rather discard the binding? The latter allows full control from within the given goal, still sounds... not very natural. (But it might be me.)

Also, a "side effect" is that now loop/1 is not anymore just any Prolog predicate. It certainly makes sense to use it as the goal for an answer source, but what should happen if it is invoked directly? Just ignore any return statements?

Julio

Julio Di Egidio

unread,
Sep 15, 2015, 8:37:37 PM9/15/15
to
Eventually, I think I have found the way. The return operation happens in the context of the worker loop, so, at the cost of using some thread-local context, return can fully participate into the worker loop...

For now I have just put together the new flow diagram:
<http://seprogrammo.blogspot.co.uk/2015/09/answer-sources-from-fluents-to.html>

I am not seeing any issues with that design and it looks like it solves all problems, i.e. we get a return operation as defined in Tarau's as well as overall the implementation approach makes again sense to me.

So, I will proceed in that direction, but any feedback welcome.

Julio

Jan Burse

unread,
Sep 20, 2015, 4:48:02 PM9/20/15
to
This guy talks so much about Iterators that I have
the feeling I could still learn something:

http://hop.perl.plover.com/book/pdf/HigherOrderPerl.pdf

But why Perl, why?



Jan Burse

unread,
Sep 29, 2015, 10:25:52 AM9/29/15
to
Julio Di Egidio schrieb:
>> I need to think more about it.
> Eventually, I think I have found the way. The return operation
> happens in the context of the worker loop, so, at the cost of
> using some thread-local context, return can fully participate
> into the worker loop...
>
> For now I have just put together the new flow diagram:
> <http://seprogrammo.blogspot.co.uk/2015/09/answer-sources-from-fluents-to.html>
>
> I am not seeing any issues with that design and it looks like it
> solves all problems, i.e. we get a return operation as defined in
> Tarau's as well as overall the implementation approach makes again
> sense to me.
>
> So, I will proceed in that direction, but any feedback welcome.
>
> Julio

So I guess you have added a return/1 statement somewhere in
your answer source wrapper somehow. But I still doubt that
it will have a wide spread adoption.

The problem is as follows. Usually in application where
Prolog is mixed with another programming language, call
this language XY, you will have call chaines such as:

XY --> Prolog --> XY --> Prolog

So the foreign language XY calls Prolog, and Prolog calls
the foreign language XY and the foreign language calls Prolog
again and so one.

Already not so easy to do in a client server setting, but
lets assume we have a tight integration. If the Prolog
is implememted as a trampolin or some such, the return/1
would just suspend the trampolin and return to the
calling site:

XY --> Prolog
calls return/1
<-- gives control back to XY


But what if the return/1 call is further down in the
call chain. For example in the second call:

XY --> Prolog --> XY --> Prolog
calls return/1
XY <-- gives control back to XY
but how can we give back control to XY?
and how can we later resume XY execution?

This is all pretty undefined. So far most foreign language
XY calls Prolog APIs only react to the following
ports of the bird box:

+------+
Call-->| |-->Exit
| |
Fail<--| |<--Redo
+------+
|
v
Error

They can detect a Fail, an Exit or an Error. For example
tuProlog has info.isSuccess(). The result of return/1 would
probably consist a new signal from the bird box. Since
the usual error result doesn't allow to resume execution.

Or we could say that an error allows to resume. But then
we are in conflict with most native foreign language
XY exception handling semantics. Most foreign language
XY exception just ripple down the call chain, and they
act very similar as the ISO catch/3 statement.

Further if we have a new error semantic somewhere, how
could we reflect the catch and resume behaviour inside
an executing Prolog interpreter. Will there be something
new besides the existing ISO catch/3 statement and the
ISO throw/1 statement. For example:

% catch_suspending(+Goal, -Error, +Goal)
catch_suspending(G1, E, G1).
% throw_resuming(+Error)
throw_resuming(T).

But implementing a catch_suspending/1 and throw_resuming/1
is a little difficult. Especially since the throw_resuming/1
doesn't have an argument with a handle to an answer source.
And the catch_suspending doesn't generate such a handle. Would
we therefore need:

% catch_suspending(+Goal, -Error, -Handle, +Goal)
catch_suspending(G1, E, H, G1).
% throw_resuming(+Handle, +Error)
throw_resuming(H, T).

Questions, Questions...

Bye



Jan Burse

unread,
Sep 29, 2015, 10:58:37 AM9/29/15
to
Jan Burse schrieb:
> Questions, Questions...

Oops, catch_suspending/3, throw_resuming/1,
catch_suspending/3, throw_resuming/2 are B.S.
doesn't make sense what I wrote.

We could of course continue the new catch/3
itself. So what we would need:

% catch_suspending(+Goal, -Error)
catch_suspending(G, E)

Which is almost the same as answer_source,
but without the handle.

Hm.

Bye





Julio Di Egidio

unread,
Sep 29, 2015, 11:15:58 AM9/29/15
to
On Tuesday, September 29, 2015 at 3:25:52 PM UTC+1, Jan Burse wrote:
> Julio Di Egidio schrieb:
>
> > For now I have just put together the new flow diagram:
> > <http://seprogrammo.blogspot.co.uk/2015/09/answer-sources-from-fluents-to.html>
> >
> > I am not seeing any issues with that design and it looks like it
> > solves all problems, i.e. we get a return operation as defined in
> > Tarau's as well as overall the implementation approach makes again
> > sense to me.
> >
> > So, I will proceed in that direction, but any feedback welcome.
>
> So I guess you have added a return/1 statement somewhere in
> your answer source wrapper somehow.

Why guess? There was a link to the flow diagram, and the flow is simply an extension of the worker loop flow already implemented in the code.

> But I still doubt that
> it will have a wide spread adoption.

Thank you, the point is, for inconsistent reasons.

> The problem is as follows.
<snip>

There is no such problem, you seem to keep missing the very point of interactors and how they work.

> Questions, Questions...

Trolling?

Julio

j4n bur53

unread,
Sep 29, 2015, 11:46:04 AM9/29/15
to
Hi,

Julio Di Egidio schrieb:
> There is no such problem, you seem to keep missing the
> very point of interactors and how they work.
>
>> >Questions, Questions...
>
> Trolling?

Taraus paper only says that return/1 can return
an arbitrary answer pattern. So a typically
foreign language XY interface, will probably
correctly handle:
no
the(A)
exception(E)

But what if I issue return(foo(bar)). Is this
allowed in your framework? How would a foreign
language XY interface look like, that also allows
such a return/1 answer pattern, and also allows
resuming after such a pattern?

Should we have a Tarau interface, and built on
top of this a Prolog interface. So that the end-user,
in case he feels a need for it, can also call this
Tarau interface. Is this the goal of your answer
source project.

Does your answer source project now allow the
Tarau interface? Would your answer source project
translate to such a Tarau interface in a foreign
language XY? How safe is it, can I confuse the
interface, for example the Prolog interface?

Bye

P.S.: I am not sure whether Taraus Paper really
works. For example he writes:

catch(Goal,Exception,OnException):-
answer_source(answer(Goal),Goal,Source),
element_of(Source,Answer),
do_catch(Answer,Goal,Exception,OnException,Source).

But if one analyses element_of, we see that a
exception(E) answer pattern would never go through.
He defines element_of as follows:

element_of(I,X):-get(I,the(A)),select_from(I,A,X).

select_from(_,A,A).
select_from(I,_,X):-element_of(I,X).

Although I fully understand the intention of Tarau,
given the fact that there are also older papers years
ago of him that showed the "interactor" concept(*), it
might contain small errors from his choice of
presentation.

An earlier paper with "interactors" is the following:
he BinProlog Experience: Architecture and Implementation Choices for
Continuation Passing Prolog and First-Class Logic Engines
http://arxiv.org/abs/1102.1178

Just have a look at 6 Logic Engines as Interactors
He mentions also CLU, He He. He mentions als yield. He He
But the paper contains the same do_catch/5 error.

j4n bur53

unread,
Sep 29, 2015, 12:05:47 PM9/29/15
to
Hi,

j4n bur53 schrieb:
> Although I fully understand the intention of Tarau,
> given the fact that there are also older papers years
> ago of him that showed the "interactor" concept(*), it
> might contain small errors from his choice of
> presentation.

Jekejeke Prolog for example uses "interactors" under
the hood to implement the ISO catch/3. It doesn't
need "interactors" for (->)/2 or (*->)/2. But I must say
is not a good solution. Since it uses the native Java
stack to invoke the "interactor".

Also other Prolog systems might have this problem.
I remember a similar question by tuProlog. It could
be that SWI-Prolog has solved the problem. To really
reach the ideal of a Lean Prolog, interaction with
the "interactor" has to be integrated into the parent
trampolin.

So the child trampolin and the parent trampolin must
merge, only then the "interactor" concept would make
any sense. If they don't merge, we might bump to the
native Java stack limitation. This is actually the
last bastion in my current Prolog system implementation,
eliminating the "interactor" for the catch/3.

The idea to eliminate the "interactor" is simple.
Extend the concept of a choice point (already partly
done) and view exception handling as a choice point
interaction (not yet completed). But when this is
done there is still some more problem left.

We have now traded the native Java stack by a choice
point. But a choice point means that the determinancy
analysis breaks down of the Prolog interpreter. But
why should a simple catch/3 disable the determinancy
analysis? So we must have different kind of choice
points, and so on and on, really difficult problem.(*)

Bye

(*)
Roumors are that the Java exception handling
was realized by a LISP veteran.


Douglas R. Miles/LogicMoo

unread,
Jan 16, 2016, 9:40:20 PM1/16/16
to
Has anyone decided a good argument to have TermSinks in prolog?

Douglas R. Miles/LogicMoo

unread,
Jan 16, 2016, 11:04:58 PM1/16/16
to
On Saturday, January 16, 2016 at 6:40:20 PM UTC-8, Douglas R. Miles/LogicMoo wrote:
> Has anyone decided a good argument to have TermSinks in prolog?


Here is my argument:



On Thu, Jan 7, 2016 at 2:20 AM, Jan Burse <burs...@gmail.com> wrote:
Hi,

> Here is the challenge. The following Expert System works
> with trail hooks. Can you do it with attribute variables? Here
> is an example session of the Expert System:

% ?- use_module(library(minimal/hypo)).

% ?- <= +motion(walk), <= +skin(fur), <= +diet(meat), animal(X).
% X = cat

% ?- animal(X).
% No

% ?- <= +diet(meat), <= +skin(fur), <= +motion(walk), animal(X).
% X = cat

As is clearly demonstrated in the above session, there was a fact animal(cat)
during the first query, in the second query it was not there, and in the
third query it was there again.



First with skolem functions:

(The method I've first used in SWI was with skolem functions (when designing an expert system)).


?- animal(X).
X= (sk1(A,diet(A,meat)) & sk3(A,skin(A, fur)) & sk2(A,motion(A, walk)) & animal(A) & _) ;
X= (sk5(A,diet(A,nonmeat)) & sk3(A,skin(A, fur)) & sk2(A,motion(A, walk)) & animal(A) & _) ;
No.



Second way is with normal attributed variables:


?- animal(X).
X=_
put_atts(X,[+diet(meat),+skin(fur),+motion(walk),+animal(),+'$atts'([termsink])).


?- integer(X).
X=_
put_atts(X,[+integer()]).



But for my tastes that was still too weak!

So the third way which was why I got involved with the whole Tarau Fluent exercise:



?- termsink(X),integer(X),X=1.
X=_
put_atts(X,[+attvar_bind(1),+integer(),+'$atts'([termsink])]).

?- termsink(X),integer(X),X=1,X=2.
No.

^----- this fails not because X=1 (X is still a term sink) it failed becasue of attvar_bind(1).


What a "term sink" does is it allows me to verify the attributes but also allows me to remain able to unify later


Just becasue I bind with 1, TermSink allowed me to not have my attributes destroyed.

(sorry for this bad example coming next)


?- termsink(X),integer(X),X=2,X=s(s(0)).

X=_
put_atts(X,[+attvar_bind(2),+integer(),+'$atts'([termsink])]).


Message has been deleted

Jan Burse

unread,
Jan 17, 2016, 9:14:37 AM1/17/16
to
Hi,

I am not sure whether showing the top-level gives
much insights here. Except if you want to highlight
certain aspects that can be already seen in the
toplevel.

But what the toplevel of an Expert System does is
a result of how you modelled the knowlegde in the
expert system and what inference mechanism you
used.

So it would also be of interest, to see how you
defined the animals rules. I find various general
approaches here:

1) using some hooks like variable_attributes/3:
The rules are modelled by Prolog clauses that
implement the predicate variable_attributes/3.
These rules will mainly implement TRAILED SIDE
EFFECTS on the attrribite variables. No
undo/1 is exposed.

2) using CHR:
https://en.wikipedia.org/wiki/Constraint_Handling_Rules
The rules would be modelled in the language of
CHR. The rules will mainly implement TRAILED SIDE
EFFECTS on the constraint store. No undo/1
is exposed.

3) using Jekejeke Minlog:
In the particular animals3 example I am using rules
in the language of Jekejeke Minlog forward chaining.
these rules have instead of the (:-)/2 operator, the
(=>)/2 operator and additional adornments such as (+)/1.
See for example here:

http://www.jekejeke.ch/idatab/doclet/prod/en/docs/15_min/10_docu/02_reference/08_appendix/example02/animals3.html
The rules will mainly implement TRAILED SIDE
EFFECTS on the knowlegde base. In the particular case
thread_local/1 facts are used. The undo/1 is exposed
somewhere else in the API, and can also be used for other
purposes if necessary.

http://www.jekejeke.ch/idatab/doclet/prod/en/docs/15_min/10_docu/02_reference/07_theory/05_system/04_trail.html

So how is this termsink used in defining the animals
knowledge? And why does animal(X) alone not fail, since
there were no facts added, so with closed world assumption
there is not enough knowledge to derive something?

Bye

Douglas R. Miles/LogicMoo schrieb:

Jan Burse

unread,
Jan 17, 2016, 9:21:23 AM1/17/16
to
Jan Burse schrieb:
> So how is this termsink used in defining the animals
> knowledge? And why does animal(X) alone not fail, since
> there were no facts added, so with closed world assumption
> there is not enough knowledge to derive something?

See here for some verbosity, why animal(X) alone fails:
http://www.jekejeke.ch/idatab/doclet/prod/en/docs/15_min/10_docu/02_reference/04_examples/02_animals.html

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 12:41:06 PM1/17/16
to
Sorry,

The +'$atts'([termsink]) was not supposed to be there :)

My new expert system was design use termsink though as a way of handle existential Skolems. These are places where the users had created a prototypical furry carnivorous animal with:

==> exists(A,and(isa(A,animal),and(skin(A,fur),and(skin(A,fur),diet(A,meat)))).

And I need to be able to bind with existing entities. I do not wish to make *every entity* A attributed variable:

pet(X,Y):-put_atts(X,+named(joe)),put_atts(X,+named(kitty)).

the system allows working with prolog databases containing:

pet(joe,kitty).



?- animal(X),pet(joe,X).
X= kitty. % X has lost it's constraints now :(


Instead I get back:

?- animal(X),pet(joe,X).
X = _
put_atts([+attr_bind(kitty),

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 12:53:03 PM1/17/16
to
On Sunday, January 17, 2016 at 6:21:23 AM UTC-8, Jan Burse wrote:
> Jan Burse schrieb:
> > So how is this termsink used in defining the animals
> > knowledge? And why does animal(X) alone not fail, since
> > there were no facts added, so with closed world assumption
> > there is not enough knowledge to derive something?

I saw no reason for the expert system I designed to be unable to understand what it does and does not know.

Take this case:

It has no evidence that animals cannot exist.
Has evidence of what makes up an animal if it di

What I want:

It can certainly create a prototype variable. Hopefully the user is not tricked into believing that is evidence of existence or not..

If the user was to interpret the meaning like you suggest, then "?- animal(X). " failing would tell the user there are no animals?

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 1:19:07 PM1/17/16
to
> If the user was to interpret the meaning like you suggest, then "?- animal(X). " failing would tell the user there are no animals?

Or in other words do you belive expert systems must be restricted to only the "negation by failure"? Or forced into a closed world assumption?


Here btw are some examples from a system I designed that has not been updated (thus is limited to skolems)

https://github.com/TeamSPoon/PrologMUD/blob/master/pack/logicmoo_base/t/examples/fol/family_inheritance.pfc#L207-L211

This system uses forward chaining witht eh ==>/1 and ==>/2 operators.. Why I bring it up .. Eileen has a unknown mother. the system deduces she has one but hasn't had an assertion about her yet (not shown) ... so in her place is a system generated reifiable term skArg1ofMother_1Fn(eileen). Once I tell assert her mother was Trudy the system will no longer have
"mother(eileen,skArg1ofMother_1Fn(eileen))"

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 1:23:22 PM1/17/16
to
Here is a link to the original announcement about my expert system:

https://groups.google.com/d/msg/comp.lang.prolog/mULC-uedPq0/LUt5F_AtIwAJ

Jan Burse

unread,
Jan 17, 2016, 1:39:11 PM1/17/16
to
Douglas R. Miles/LogicMoo schrieb:
>> If the user was to interpret the meaning like you
> suggest, then "?- animal(X). " failing would tell
> the user there are no animals?

The meaning in the animal.p and animal3.p example
of the predicate animal/1 is:

animal(X): X is the animal the evidence is given for.
evidence is given by a couple of facts.

> Or in other words do you belive expert systems
> must be restricted to only the "negation by failure"?
> Or forced into a closed world assumption?

I don't say that we want here NAF, the example is
not meant for negation at all:

?- \+ animal(X).
Yes

I only require:

?- animal(X).
No

if no evidence is given. I don't think your expert
system works correctly. The above No is a pure Horn
Clause result, meaning "no derivation" available.

My post was maybe a little missleading that I
mentioned "closed world assumption". What I really
want to know why you don't get a "No", meaning
"no derivation".

It seens you get some pending attributes, and hence
a "Yes". But what are these pending attributes about?
animal.p and animal3.p must work the same, except
than in animal3.p the evidence is given in the query.

Here is animal.p:
http://www.jekejeke.ch/idatab/doclet/prod/en/docs/05_run/10_docu/02_reference/08_appendix/example01/animals.html

You see all Horn Clause, no negation at all. CWA
or NAF no issue at all. "No" at the top-level is
simply the interpreter saying finitely failed
derivation tree:

See slide 9: Forests for a definition of "finitely failed"
https://www.inf.tu-dresden.de/content/institutes/ki/cl/study/winter08/flp/slides/6.pdf

Bye

Jan Burse

unread,
Jan 17, 2016, 1:45:20 PM1/17/16
to
Hi,

Jan Burse schrieb:
>
> ?- animal(X).
> No
>
> if no evidence is given.

Or if the rules cannot produce an animal from
the evidence, even if some evidence
is given.

The rules might be incomplete, viewed from
the domain. But this is a no issue here
as well.

The issue here is undo/1.

Bye

Jan Burse

unread,
Jan 17, 2016, 1:55:50 PM1/17/16
to
Jan Burse schrieb:
> In the particular animals3 example I am using rules
> in the language of Jekejeke Minlog forward chaining.
> these rules have instead of the (:-)/2 operator, the
> (=>)/2 operator and additional adornments such as (+)/1.
> See for example here:

Oops, wrong, I am using the (<=)/2 operator. Note
(:-)/2 is also a right to left arrow, similarly to
(<=)/2.

Other expert systems(*) use for example the (==>)/2
operator. But what I want to highlight is that my
forward chaining rules are also Horn Clauses.

And that forward chaining, and its internal use
of undo/1, is just a different logic control
mechanism. But the logic is still Horn Clauses.

So if there is skolem functions somewhere, then
there is either something wrong, or the approach
is indirect, somehow by moving some clauses
to the other side of the derivation sign, but
still then no skolem functions are need, it is
also wrong then.

Horn Clauses don't need skolem functions. You
only need skolem functions when converting a
logic theory in clauses and you get some
forms of alternating quantifiers. The animals
example is not intended to use alternating
quantifiers anyway. This is out of scope.

The animals example is really a blonde (sorry)
logic problem. As dumb as it could be, what the
requirements for the logic are. The issue is
undo/1 and control of logic.

Bye

(*)
Building Expert Systems in Prolog
by Dennis Merritt
http://www.inf.fu-berlin.de/lehre/SS09/KI/folien/merritt.pdf

j4n bur53

unread,
Jan 17, 2016, 3:46:31 PM1/17/16
to
Douglas R. Miles/LogicMoo schrieb:
> Here is a link to the original announcement about my expert system:
>
> https://groups.google.com/d/msg/comp.lang.prolog/mULC-uedPq0/LUt5F_AtIwAJ
>

I don't really understand what your link provides. Conversion
of FOL to clauses and different interchange formats?
Does it also provide a theorem prover base on clauses, or
any other kind of theorem prover?

Basically the animals3.p example can also be formulated
with embedded implication instead of the posting operator.

You should be able to readily verify the following with
almost any theorem prover, where (->)/2 would be the implication
in your theorem prover and (&)/2 would be the conjunection
in your theorem prover:

Your TP: motion(walk) & skin(fur) & diet(meat) -> animal(X).
X = cat

Your TP: animal(X).
No

Your TP: diet(meat) & skin(fur) & motion(walk) -> animal(X).
X = cat

The input to the theorem prover would include besides the
queries, whereby not all theorem provers can answer multiple
questions, you might need to restart the theorem prover, the
following background theory:

Your TP:
class(mamal) <- motion(walk) & skin(fur).
class(fish) <- motion(swim) & skin(scale).
class(bird) <- motion(fly) & skin(feather).

animal(rodent) <- class(mamal) & diet(plant).
animal(cat) <- class(mamal) & diet(meat).
animal(salmon) <- class(fish) & diet(meat).
animal(eagle) <- class(bird) & diet(meat).

A theorem prover will use its own clause store, agenda etc..
It will implement maybe some resolution theorem proving
whatever, using input or unit resultution, whatever etc..

The example is extremely primitive, since the background
theory is certainly datalog, so one might be able to
convert it into propositional logic and use a SAT solver
maybe.

The queries are also extremly primitive, the only free
variable is X, it occurs possitively in the query. The
free variable X doesn't need skolemization for answer
extraction. Answers are determinstic, you wont get
X = T1 | .. | X = Tn.

The interesting thing of undo/1 is now that you can
do this theorem proving inside Prolog, and invoke from
Prolog, according to the ideas represented in the SATCHMO
paper by Bry.

Moreover using undo/1 here will allow to implement
something else than the usual backward chaining of Prolog,
we wouldn't need undo/1 for that, and just invoke Prolog.
What is facinating in my opinion is that we can kick start
forward chaining from the top-level or from anywhere
in the code.

The forward chaining will not be exactly as one is used
from resolution theorem proving, i.e. unit resolution.
Its a variant of it which also has some drawbacks.

But in Jekejeke Minlog it is just a combination of a
hypothetical reasoning module and a delta rules
rewriting module. Both make use of undo/1.

Bye


Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 4:19:18 PM1/17/16
to
JanB,

> quantifiers anyway. This is out of scope.

Yes, so. anyways I hope I did answer your your earlier question as to the why *I* needed term sinks for my work. For a deeper answer: A Rapid Knowledge Formation project inference engine in which I developed in 1999, I canonicalized CYC language to CNF/SNF and retained even the negative units (A trick shown by M Stickel's PTTP) sometimes I could not eliminate skolem's. So I learned to live them. But we also found a way to solve the problems skolem's create using attributed variables + Paul's Sink Fluents.

You are right: our interpretations of animal/1 were different. I was sort of was mixing in Triska's thoughts about:

?- integer(X),X=1.
could almost be equivalent to
?- X=1,integer(X).

I was treating animal/1 like that use integer/1 where failure would not be useful.


About scope: I do not believe it is possible to create all of Paul's Fluent types without also creating all of Paul's Fluent types. I don't think it's a good idea to selectively leave out part of the library you don't have uses for today.. (For instance I have uses for parts of Paul's library that are different than yours, just like your uses might be different from Julio's) Also I do not think undo/1 is sufficient to implement EmptyTermSinkFluent.


BTW: I do appreciate the helpful links as you have been doing.

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 4:42:04 PM1/17/16
to
On Sunday, January 17, 2016 at 12:46:31 PM UTC-8, j4n bur53 wrote:
> Douglas R. Miles/LogicMoo schrieb:
> > Here is a link to the original announcement about my expert system:
> >
> > https://groups.google.com/d/msg/comp.lang.prolog/mULC-uedPq0/LUt5F_AtIwAJ
> >
>
> I don't really understand what your link provides. Conversion
> of FOL to clauses and different interchange formats?
> Does it also provide a theorem prover base on clauses, or
> any other kind of theorem prover?


Oops The question at the link was if anyone disagreed with the conversions. It was not an announcement sorry.. I was thinking it had contained a link to the system:

https://github.com/TeamSPoon/PrologMUD/tree/master/pack/logicmoo_base/prolog/logicmoo


This is an expert system identical to LarKC (thus CYC) except bent towards compatibility of Common Logic Interchange Format instead of CycL but written to run on SWI-Prolog.

It was also showing the use of prolog forward chaining (Tim Finnin's PFC) + First order logic as well as higher order logics. (Much like CycL) with a datalog I based on with sprinkle of XSB Prolog's WFS Well Founded semantics

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 5:07:24 PM1/17/16
to

> This is an expert system identical to LarKC (thus CYC) except bent towards compatibility of Common Logic Interchange Format instead of CycL but written to run on SWI-Prolog.

The closest thing to documentation about the system is:

https://github.com/TeamSPoon/PrologMUD/tree/master/pack/logicmoo_base#part-b---predicate-calc


I do like how in your system Jekejeke Minlog you set up a easy way to load a preload a query with conjecture:

?- <= +motion(walk), <= +skin(fur), <= +diet(meat), animal(X).

Much more concise then many other things out there

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 5:45:49 PM1/17/16
to
JanB,

Don't get me wrong I like undo/1.

So much so I even made a patch for SWI-Prolog to give it undo/1.

See code at @ https://groups.google.com/forum/#!topic/swi-prolog/0rwsiI_8Uxo

You got it.. Just up to JanW to include it or not.

After I did that.. I was attempting to hijack this "Fluent Sources" thread with and see what people had for an opinion "Fluent Sinks" .. So someone besides me would sell the prolog community on Paul's fluents .. Thus sell JanW that "Fluent Sinks" are good.

What made it confusing, JanB, is I misappropriated your animal/1 example to how *my* expert system works using termsink/1 :)

-Douglas

j4n bur53

unread,
Jan 17, 2016, 7:42:54 PM1/17/16
to
Douglas R. Miles/LogicMoo schrieb:
> See code at @https://groups.google.com/forum/#!topic/swi-prolog/0rwsiI_8Uxo
>
> You got it.. Just up to JanW to include it or not.

Cool!

Here are some more test cases (done in Jekejeke Minlog):

?- use_module(library(experiment/trail)).

?- (F=foo;F=baz),sys_unbind((write('before undo F = '),write(F),nl)),
write(bar), nl.
bar
F = foo ;
before undo F = foo
bar
F = baz
before undo F = baz

?- (F=foo;F=baz),sys_unbind((write('before undo F = '),write(F),nl)), !,
write(bar), nl.
bar
F = foo
before undo F = foo

j4n bur53

unread,
Jan 17, 2016, 8:15:21 PM1/17/16
to
What can be quite confusing, is the error handling
for the undo/1. I am collecting exceptions that
are thrown during subsequent unbinds. They are
consed via cause/2.

?- F=foo,sys_unbind(throw(bar)), sys_unbind(throw(baz)).
F = foo
Unknown exception: baz
Unknown exception: bar

/* strange case I */
?- catch((F=foo, sys_unbind(throw(bar)), sys_unbind(throw(baz))),
E, true).
F = foo
Unknown exception: baz
Unknown exception: bar

/* strange case II */
?- catch((F=foo, sys_unbind(throw(bar)), sys_unbind(throw(baz)), fail;
true), E, true).
E = cause(baz,bar)

Since the catch/3 is choice point based, and I have
a determinism check optimization, that doesn't keep
the error handler of catch/3 if the first argument
has produced a determinsitic solution.

As a result, the catch/3 is not able to catch the
error in case I, but only in case II. What could be
done, is checking also for unbinds on the trail not
only for the existence of choice points, when determining
determinancy.

But checking the trail is possibly costly, since the
trail is not a thing where such a check can be easily
done, for each surround catch/3 it starts somewhere else,
and it might be quite long, hanving other stuff in it
than only unbind hooks.

Not sure what to do about it.
This is currently s little imperfection.

j4n bur53 schrieb:

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 9:27:19 PM1/17/16
to
> done.


Speaking of costly for the swi patch I'd almost rather had..

/*********************
* UNDO HOOK *
********************/
/*
?- F='\n',undo(((writeln(F:1);writeln(F:2)),fail)),!,write(before),fail.
*/
system:'$meta'('$undo_unify', _, Goal, 1):- '$schedule_wakeup'(Goal).
'$undo_unify':verify_attributes(_,_,[]).
undo(GoalIn):-
metaterm_options(W,W), ON is W \/ 8, % Flag to turn on trail scanning
( ON == W
-> GoalIn=Goal ; % was already on
(metaterm_options(_,ON), Goal=(metaterm_options(_,W),GoalIn))),
put_attr(Var,'$undo_unify',Goal),Var=Goal.





for each surround catch/3 it starts somewhere else,
> and it might be quite long, hanving other stuff in it
> than only unbind hooks.
>
> Not sure what to do about it.
> This is currently s little imperfection.
>



Here is a slightly underhanded trick:

You could temporarily override your definition of sys_unbind/1,
the $ preds are the Java trampolines


sys_unbind(G):- $sys_unbind(G).

catch(G,E,H):-
asserta((sys_unbind(U):- !, $sys_unbind(catch(U,E,H))),Ref),
$sys_unbind(erase(Ref)),
$catch(G,E,H).




> j4n bur53 schrieb:
> > Cool!
> >
> > Here are some more test cases (done in Jekejeke Minlog):
> >
> > ?- use_module(library(experiment/trail)).
> >
> > ?- (F=foo;F=baz),sys_unbind((write('before undo F = '),write(F),nl)),
> > write(bar), nl.
> > bar
> > F = foo ;
> > before undo F = foo
> > bar
> > F = baz
> > before undo F = baz
> >
> > ?- (F=foo;F=baz),sys_unbind((write('before undo F = '),write(F),nl)), !,
> > write(bar), nl.
> > bar
> > F = foo
> > before undo F = foo


Thank you for the example tests.

-Douglas

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 9:52:56 PM1/17/16
to
On Sunday, January 17, 2016 at 5:15:21 PM UTC-8, j4n bur53 wrote:
> What can be quite confusing, is the error handling
> for the undo/1. I am collecting exceptions that
> are thrown during subsequent unbinds. They are
> consed via cause/2.

One other trick without asserta (also provides a portable catch)



:- nb_setval('$my_handler',[h(Ex,$throw(Ex)])).
:- nb_setval('$my_unbinder',u(G,$sys_unbind(G))).

sys_unbind(U):- b_getval('$my_unbinder',u(U,C)),C.

throw(E):- b_getval('$ex_handler',List),member(h(E,H),List), H.


catch(G,E,H):-
b_getval('$ex_handler',Previous),
b_setval('$ex_handler',[h(E,H)|Previous]),
b_getval('$my_unbinder',UPrevious),
b_setval('$my_unbinder',u(U,catch(U,E,H))),
G,
nb_setval('$my_unbinder',UPrevious).
nb_setval('$ex_handler',Previous).

Douglas R. Miles/LogicMoo

unread,
Jan 17, 2016, 10:21:47 PM1/17/16
to
My so called "portable catch" was a failure above as it'd is missing the block/3 exit/1 but you probably still catch the drift of the b_setval/b_getval.

Mainly I was going along my belief is that catch/3 and call/1 themselves should not attempt to be grouping choice points :) but merely provide the next set of instructions.

Jan Burse

unread,
Jan 23, 2016, 7:09:42 PM1/23/16
to
Hi,

Douglas R. Miles/LogicMoo schrieb:
> Has anyone decided a good argument to have TermSinks in prolog?

Are TermSinks somewhere in the making?

Douglas R. Miles/LogicMoo schrieb:
> Here is my argument:
> % ?- <= +motion(walk), <= +skin(fur), <= +diet(meat), animal(X).
> % X = cat

I doubt that TermSinks are helpful here.

On the other hand, here is the challenge, can you do:
(from the Java AbstractList implementation)

public boolean equals(Object o) {
if (o == this)
return true;
if (!(o instanceof List))
return false;

ListIterator<E> e1 = listIterator();
ListIterator<?> e2 = ((List<?>) o).listIterator();
while (e1.hasNext() && e2.hasNext()) {
E o1 = e1.next();
Object o2 = e2.next();
if (!(o1==null ? o2==null : o1.equals(o2)))
return false;
}
return !(e1.hasNext() || e2.hasNext());
}

I found it hard to do, assuming the two lists are
answer sources. Problem is that cursor piggybacking
doesn't work, somehow the interpreter has to
be forked.

Something else, do you mean TermSinks or TermSources?
TermSinks looks to me rather as a means to realize
a findall/3 predicate.

TermSources seem to me redundant to AnswerSources, you
can just define for example a shallow term sources
as follows:

shallow_arguments(Term, Arg) :-
Term =.. [_|List],
member(Arg, List).

Turn the above into an answers source. Now assume
you have two answer sources, could you implement equals()
for example via SWICLI (equals implemented in C# .NET with
the help of SWICLI, working for given answer sources)?

What is the model behind SWICLI calling Prolog? (In
one place I saw something similar to a currentInterpreter()
method, which I have only introduced in release 1.0.10
in Jekejeke Prolog)

Bye

P.S.:
Test cases,
using closures (i.e. shallow_arguments(foo(1,2,3))
would be an answer source for shallow_arguments(foo(1,2,3),X) with
X the result variable)

Test case 1:
equals(shallow_arguments(foo(1,2,3)),
shallow_arguments(bar(1,2,3))) --> true

Test case 2:
equals(shallow_arguments(foo(2,2,1)),
shallow_arguments(bar(2,1,1))) --> false

Test case 3:
equals(shallow_arguments(foo(1,2,3)),
shallow_arguments(bar(1,2))) --> false

Etc..

P.P.S.:
I was able to deliver something for Jekejeke Prolog
that could, its an instance of the combiner pattern:

http://www.jekejeke.ch/idatab/doclet/prod/docs/05_run/10_docu/03_interface/04_examples/07_combine.html

It doesn't have to make use of currentInterpreter(), but
it could also call that. But currentInterpreter() doesn't
give a thread local controller, but rather nothing as
long as not called from within the next() of an iterator.

Jan Burse

unread,
Jan 23, 2016, 7:32:36 PM1/23/16
to
Jan Burse schrieb:
>
> Something else, do you mean TermSinks or TermSources?
> TermSinks looks to me rather as a means to realize
> a findall/3 predicate.

Jinnis world:
http://logic.csci.unt.edu/tarau/resources/kprolog/docs/tarau/jinni/package-summary.html

Jan Burse

unread,
Jan 23, 2016, 7:58:49 PM1/23/16
to
Jan Burse schrieb:
> Douglas R. Miles/LogicMoo schrieb:
> > Here is my argument:
>> % ?- <= +motion(walk), <= +skin(fur), <= +diet(meat), animal(X).
>> % X = cat
>
> I doubt that TermSinks are helpful here.

Well, yes and no. Electrons would be also helpful, since
computers run on electrons. He He. Thats the problem with
too primitive notions, sink, source, they are everywhere.

Bye

Douglas R. Miles/LogicMoo

unread,
Feb 27, 2016, 12:57:00 PM2/27/16
to
Correct

http://logic.csci.unt.edu/tarau/resources/kprolog/docs/tarau/jinni/Sink.html

Though this assumes (in my impl) when I unify(.) to a Sink I trail to Prog then putElement(.) . I ended up doing this in Paul's MultiVar

Jan Burse

unread,
Jun 12, 2016, 2:28:48 PM6/12/16
to
Julio Di Egidio schrieb:
> Hi all,
>
> I have implemented an initial version of Answer Sources in Prolog (SWI).

Dear All,

Made a long due experiment in fair logical operators. In functional
programming languages these are already known for a while. In logic
programming there are issues besides realizing Tarau's interactors. One
of the main problem is how to deal with shared variables and we opted
for goals with binders. We use the binder (\)/2 form our module abstract.

The following fair logic operators according to Oleg Kiselyov LogicM
were implemented:

Fair Disjunction interleave/3:
This predicates interleaves a disjunction. It takes two goals with
binders and alternatively binds the result of the goals in the third
argument. It only allocates two micro engines for the whole process.

Fair Conjunction >>-/3:
This predicate computes a product. It takes two goals with binders
and binds both results of the goals in the third argument. It first
allocates a micro engine for the first goal. And then for each solution
it needs to copy the second goal and also invoke a fair disjunction.

Open Source: Fair Experiment
http://gist.github.com/jburse/c8f87214b96b48f3aa2263c25b94e4ae#file-fair-p

Google+ Screenshot: Fair Experiment
http://plus.google.com/+JekejekeCh/posts/YnwqfbotC8s

At the end of the Google+ post there is also a link to the new module
micro. One will immediately recognize the resemblage of the API with
Java iterators. We will probably integrate the fair experiment in the
CLP(FD) solver to enumerate infinite domains.



Jan Burse

unread,
Jun 12, 2016, 2:59:14 PM6/12/16
to
Jan Burse schrieb:
> The following fair logic operators according to Oleg Kiselyov LogicM
> were implemented:

BTW: I speculate there is a much better fair conjunction arround,
that creates much less overhead.

Pictural it would be an interleave of the following separation
of the square into two parts:

...
******_
*****__
****___
***____
**_____
*______...

-- and --

...
______*
_____**
____***
___****
__*****
_******...

Each part can be enumerate as follows:

call_nth(G1, N), call_upto(G2, N).

respectively:

call_nth(G2, N), M is N-1, call_upto(G1, M).

All that is needed is to interleave the two. But I didn't
try yet this method. But it might also give a much more
balanced enumeration of two infinite predicates.

Currently two infinite predicates in Oleg Kiselyov LogicM
give a quite unbalanced picture.

But this method would probably nevertheless need lambda
abstraction like copy of both sides of the conjunction, and
the counters. So the initial effort could be higher, even
if the extra effort is flat later on.

Bye


j4n bur53

unread,
Jun 13, 2016, 5:29:45 AM6/13/16
to
Jan Burse schrieb:
BTW, these micro engines are not only zero threads,
means they are just trampoline objects existing in
the same single thread. Or in multi-threaded application
each thread can use multiple micro engines.

Micro engines are further zero copying and zero queuing.
If one creates a micro engine via:

micro_new(R, G, E).

Then R and G are not copied. Only a new iterator handle
E is generated, and a reference to R and G is stored in
the handle. Then if one accesses a solution via:

micro_next(E, S)

also no copying or dequeing happens. Only the store R
reference which might now point to an instantiated R,
is unified with S. Thats all.

So they are ultra light weight. Tarau's get_answer/2
has been replaced by the two predicates micro_has_next/1
and micro_next/2 according to the Java iterator interface.

boolean hasNext()
E next()
http://docs.oracle.com/javase/7/docs/api/java/util/Iterator.html

The remove() is not supported. But a further API is micro_close/1
in asfar the micro engines also implement the Java closeable
interface:

void close()
http://docs.oracle.com/javase/7/docs/api/java/io/Closeable.html

The close() API makes micro engines a little bit more complicated
than oridinary Java iterators. Ordinary Java iterators usually
don't need a close. You just forget about them and GC will
do its work.

Here we need a close() since we might to abort search at some
moment. We adopted the trailing of the close() from Tarau. And
we use our equivalent to SICSTus undo/1 for this purpose.

This is one reason why micro engines are currently only part of
Jekejeke Minlog and not of the Jekejeke Runtime. The use of our
equivalent to SICStus undo/1 is seen here:

sys_assume_micro/3 which does the trailing à la Tarau
http://www.jekejeke.ch/idatab/doclet/blog/en/docs/15_min/02_reference/minimal/assume.html?hash=sys_assume_micro/3

The trailing code is:

sys_assume_micro(R, G, E) :-
sys_atomic(( micro_new(R, G, E),
sys_unbind(micro_close(E)))).


j4n bur53

unread,
Jun 13, 2016, 5:34:38 AM6/13/16
to
j4n bur53 schrieb:
> Then R and G are not copied. Only a new iterator handle
> E is generated, and a reference to R and G is stored in
> the handle. Then if one accesses a solution via:
>
> micro_next(E, S)
>
> also no copying or dequeing happens. Only the store R
> reference which might now point to an instantiated R,
> is unified with S. Thats all.

With the "illogical behaviour":

?- [user].
p(a).
p(b).

?- micro_new(_, p(X), E), micro_next(E, _), write(X), nl,
micro_next(E, _), write(X), nl.
a
b

So the variable X dynamically changes its binding during
the execution. Violating "variable monotonicity", having
a kind of "side effect".

But micro engines are allowed to do this, nevertheless
we can bootstrap more logical operators via them, like
the shown interleave/3 or >>-/3.

I am planning some expermiment to eliminate the binders
and the result argument as well in interleave/3 and >>-/3,
so that we only have interleave/2 and >>-/2.

Work in progress.

Bye

Jan Burse

unread,
Jun 13, 2016, 11:43:01 AM6/13/16
to
j4n bur53 schrieb:
> Micro engines are further zero copying and zero queuing.
> If one creates a micro engine via:
>
> micro_new(R, G, E).

Without binders, which are usally already assumed to have distinct
variables, I need nevertheless copying to make the fair disjunction
goals distinct. So the prospective isn't really that extremly
bright. Still investigating what the options are.

Jan Burse

unread,
Jun 17, 2016, 6:28:00 AM6/17/16
to
Bad News: We loose Forward Checking
Our interleave/2 and >>-/2 predicate implementation makes use of micro
engines. Micro engines share the constraint store of their parent micro
engine, but currently they cannot store and restore updates to the
constraint store. We therefore loose forward checking. See second
screenshot.

What does it mean that we loose forward checking. Basically it means
that the fair disjunction and conjunction is blind towards propagation
of variable instantiation through the constraint model. In the second
screenshot enumerating only X and Y is fast, since the constraint model
will determine Z by bisection.

But when we enumerate X, Y and Z, we see an extreme slowdown. Problem is
that Z is part of the enumeration since the fair disjunction and
conjunction use copying and unification. Through the copying the
enumeration happens ins some extra variables for each micro engine, and
only through unification the X,Y and Z are later given their values. It
seems at a too late moment.

Micro Engine Cantor Pairing hinders Forward Checking
https://plus.google.com/+JanBurse/posts/4zWKndhQTGT

Jan Burse schrieb:

Jan Burse

unread,
Jun 17, 2016, 6:39:48 AM6/17/16
to
Hi,

Maybe a last resort to nevertheless use fair disjunction and
conjunction would be to implement them not only with micro engines
but also with delemited continuation, assumingly the delemited
continuation can also capture and resume constraint store updates.

But delemited continuation that simply captures and resumes
backtracking is already a non-trivial engine implementation
change, which even induces some extra offort in redoing the
clause instantiations choice point creations along the called path.

A delemited continuation that is also redoing constraint store
changes needs even more engine implementation changes. Was thinking
of an inbetween solution, where we don't work with delemited
continuation, but add copy_term/3 to the fair disjunction and
conjunction.

But a simple check shows that copy_term/3 is possibly also no
solution. Independent which variable X, Y or Z I pick, my
copy_term/3 gives me the whole constraint model, since all 3
variables are contected in the example by the following
constraint (pythagorean pairs is it):

X*X + Y*Y #= Z*Z

So copy_term/3 doesn't help, its not local enough. What would
help would be an internal API that is an extension of the undo/1
predicate. So that the micro engine tells us the changes it did
to the constraint store. And further control which would allow
us to undo these changes and replay these changes.

Meanwhile I will try call_nth/2 and call_upto/2 to get a
pragmatic solution. Still call_nth/2 and call_upto/2 can be
specialized to the enumeration at hand. So it might be not
that expensive to enumerate this way.

Bye

Jan Burse schrieb:

Douglas R. Miles/LogicMoo

unread,
Jan 6, 2017, 3:53:46 PM1/6/17
to
Hi Julio,

I noticed a small problem in the answer sources library:



13 ?- source_open(X, member(X,[A,B,C]), S1).
S1 = source(t0, 7).


14 ?- source_enum($S1, answer(_, the(X))),writeq(X).
_76
S1 = source(t0, 7) ;
_6
S1 = source(t0, 7) ;
_6
S1 = source(t0, 7) ;

Notice in the last two results they ended up being the same variable:

The answer I expected back was:

14 ?- source_enum($S1, answer(_, the(X))),writeq(X).
_76
S1 = source(t0, 7) ;
_6
S1 = source(t0, 7) ;
_91
S1 = source(t0, 7) ;

Just letting you know and if you've patched it since..

Thank you in advance!

Douglas R. Miles

Julio Di Egidio

unread,
Jan 10, 2017, 11:57:28 AM1/10/17
to
On Friday, January 6, 2017 at 9:53:46 PM UTC+1, Douglas R. Miles/LogicMoo wrote:
> Hi Julio,
>
> I noticed a small problem in the answer sources library:
>
> 13 ?- source_open(X, member(X,[A,B,C]), S1).
> S1 = source(t0, 7).
>
> 14 ?- source_enum($S1, answer(_, the(X))),writeq(X).
> _76
> S1 = source(t0, 7) ;
> _6
> S1 = source(t0, 7) ;
> _6
> S1 = source(t0, 7) ;
>
> Notice in the last two results they ended up being the same variable:

Hi Douglas,

I rather get three time the same variable:

% SWI-Prolog (Multi-threaded, 32 bits, Version 7.3.25)

?- source_open(X, member(X, [A,B,C]), S1).
S1 = source(t0, 1).

?- source_enum($S1, answer(_, the(X))),writeq(X).
_G4940
true ;
_G4940
true ;
_G4940
true ;
false.

which is the result I would expect: it is the same one X...

But I may be wrong, it's a while I have not worked on this project.

What would you say, is it worth bringing it to completion? To begin with,
I could put the whole thing on GitHub if there is interest.

Julio

Douglas R. Miles/LogicMoo

unread,
Jan 13, 2017, 5:36:56 PM1/13/17
to
I think it is work it!

As far as whether or not it should be the same X variable I think I agree it should be the same X.

Though think of the case that might act the same way if it (member/2) was used outside of an engine.



And of course whatever the solution, we'd not want this to foul up the works: (which I assume doesn't)

?- source_open(X,(dif(A,B),dif(A,C),dif(B,C),member(X,[A,B,C])), S1).

Julio Di Egidio

unread,
Jan 14, 2017, 7:25:34 AM1/14/17
to
On Friday, January 13, 2017 at 11:36:56 PM UTC+1, Douglas R. Miles/LogicMoo wrote:
> On Tuesday, January 10, 2017 at 8:57:28 AM UTC-8, Julio Di Egidio wrote:
> > On Friday, January 6, 2017 at 9:53:46 PM UTC+1, Douglas R. Miles/LogicMoo wrote:
<snip>
> > > Notice in the last two results they ended up being the same variable:
> >
> > Hi Douglas,
> >
> > I rather get three time the same variable:
> >
> > % SWI-Prolog (Multi-threaded, 32 bits, Version 7.3.25)
> >
> > ?- source_open(X, member(X, [A,B,C]), S1).
> > S1 = source(t0, 1).
> >
> > ?- source_enum($S1, answer(_, the(X))),writeq(X).
> > _G4940
> > true ;
> > _G4940
> > true ;
> > _G4940
> > true ;
> > false.
> >
> > which is the result I would expect: it is the same one X...
> >
> > But I may be wrong, it's a while I have not worked on this project.
> >
> > What would you say, is it worth bringing it to completion? To begin with,
> > I could put the whole thing on GitHub if there is interest.
>
> I think it is work it!

OK, as soon as I manage I will at least put it on GitHub with an updated TODO
list, and then of course I will also be accepting pull requests... Under GPL
unless someone gives reasons to do otherwise.

> As far as whether or not it should be the same X variable I think I agree it
> should be the same X.
>
> Though think of the case that might act the same way if it (member/2) was
> used outside of an engine.

Here it is:

?- member(X, [A,B,C]), writeq(X).
_G2104
X = A ;
_G2107
X = B ;
_G2110
X = C.

So you are right, it's different: I am not really sure, it's been a while
and I should think more about it... FWIW, I was pretty convinced at the time
that it works in fact correctly (relative to the intended semantics, whatever
that was...), and here is a basic variant that shows that bindings work:

?- source_open(X, member(X,[a,b,c]), S1).
S1 = source(t0, 3).

?- source_enum($S1, answer(_,the(X))), writeq(X).
a
X = a ;
b
X = b ;
c
X = c ;
false.

> And of course whatever the solution, we'd not want this to foul up the works:
> (which I assume doesn't)
>
> ?- source_open(X,(dif(A,B),dif(A,C),dif(B,C),member(X,[A,B,C])), S1).

That's trickier, my engines of course duplicate input terms and I have not
investigated if that works with attributed variables...

Anyway here it is: would you think this is correct?

?- source_open(X,(dif(A,B),dif(A,C),dif(B,C),member(X,[A,B,C])), S1).
S1 = source(t0, 1).

?- source_enum($S1, answer(_,the(X))), writeq(X).
_G2394
dif(X, _G2730),
dif(X, _G2736),
dif(_G2736, _G2730) ;
_G2564
dif(X, _G2900),
dif(_G2905, _G2900),
dif(_G2905, X) ;
_G2734
dif(_G3069, X),
dif(_G3075, _G3069),
dif(_G3075, X) ;
false.

Julio

Julio Di Egidio

unread,
Jan 22, 2017, 6:26:58 PM1/22/17
to
On Thursday, September 3, 2015 at 4:09:47 AM UTC+2, Julio Di Egidio wrote:

> I have implemented an initial version of Answer Sources in Prolog (SWI).

I have just now published version 1.2.0-beta on GitHub under GPL:
<https://github.com/jp-diegidio/Nan.System.Sources-Prolog>

This is also now available as a SWI-Prolog pack:

?- pack_install(nan_system_sources).

Please see the README file on GitHub for details.

In the hope it is useful!

Thank you,

Julio
0 new messages