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

Answer Sources in Prolog (SWI) - Preview

518 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