Programming without recursivity

133 views
Skip to first unread message

Fabrice Bizec

unread,
May 14, 2016, 11:47:42 AM5/14/16
to SWI-Prolog
Hello,

When i was a student, i realized that some of the other students could not learn the concept of recursivity.

Very basic prolog users should writes programs without to deal with it for a time.

So why don't trying to make systems that solve problems with logic or functionnal programming without using recursivity from front end side ?

That is what i have tried to do with a very little engine which solve the problem 'the just count' where from a reduced list of integers 

[1, 60, 8, 3] by example, the goal is to found a number resulting of (+, -, *, /) from integers in the list, 50 by example, that is (60 - ((3 - 1) + 8)).

Here is the predicates from user side (this is only a basic prototype for the idea) :


op(add, X, Y, RES) :-
 RES
is X + Y.


op
(sub, X, Y, RES) :-
 X
> Y,
 RES
is X - Y.


op
(mul, X, Y, RES) :-
 RES
is X * Y.


op
(add, X, Y, RES) :-
 X
>= Y,
 RES
is div(X, Y).

countAction
([L, HISTO], [RES, [op(OPcode, NUM1, NUM2)|HISTO]]) :-
 length
(L, Llength),
 
Llength >= 2,
 
select(NUM1, L, Linter),
 
select(NUM2, Linter, Lres),
 op
(OPcode, NUM1, NUM2, NUMres),


 
%the user have to append those 3 lines for optimisation
 sort
([NUMres|Lres], RES),
 
\+ histo(RES),
 asserta
(histo(RES)).


goodCount
(X, [GoalCount]) :-
 member
(GoalCount, X).

main
:-
 solver
(countAction, goodCount, [9, 50, 3, 16, 3, 8], [1400], HISTO),
 writeln
(HISTO).

And the little engine :

%
% SYSTEM PART THAT THE BASIC PROLOG PROGRAMMER SHOULD NOT SEE
%


isSolved
(_, _, [], _) :- !, fail.
isSolved
(P, Pargs, [[INLIST|HISTO]|_], HISTO) :-
 call
(P, INLIST, Pargs).
isSolved
(P, Pargs, [_|L], HISTO) :-
 isSolved
(P, Pargs, L, HISTO).


solverSub
(_, [], []).
solverSub
(GENE, [X|Lnodes], LRES) :-
 findall
(FREE, call(GENE, X, FREE), LLRES),
 solverSub
(GENE, Lnodes, LINTER),
 append
(LLRES, LINTER, LRES).


solver
(GENE, SUCCESS, NODE_INIT, LargSuccess, HISTO):-
 
dynamic(histo/1),
 
dynamic(this/1),
 retractall
(histo(_)),
 retractall
(this(_)),
 
NODESinit = [[NODE_INIT, []]],
 asserta
(this(NODESinit)),
 repeat
,
 
this(Lnodes),
 solverSub
(GENE, Lnodes, LRES),
 retractall
(this(_)),
 asserta
(this(LRES)),
 isSolved
(SUCCESS, LargSuccess, LRES, HISTO).

This is just the illustration of the concept.

What do you think of it ?


Barb Knox

unread,
May 14, 2016, 9:22:54 PM5/14/16
to SWI-Prolog, Fabrice Bizec
On 15 May 2016, at 03:47, Fabrice Bizec <fbi...@gmail.com> wrote:

Hello,

When i was a student, i realised that some of the other students could not learn the concept of recursivity.
(It's called "recursion".)

Very basic prolog users should writes programs without to deal with it for a time

That's an opinion with which I strongly disagree.  If by "basic prolog user" you mean someone whose head is full of Basic (or C, or Java, or Fortran ...) then indeed some therapy will be necessary to cure them of their unconscious misconception that all programming languages are or should be like that; but pandering to the misconception is not helpful.

Instead, I prefer to introduce Prolog via declarative readings of Prolog programs, which is something that will not remind them of Basic etc.

A good simple example is the (recursive) append predicate:

%%  append(?List1, ?List2, ?List1AndList2)
%
%   List1AndList2 is the concatenation of List1 and List2
%
append([], Ys, Ys). 
append([X|Xs], Ys, [X|Zs]) :- 
   append(Xs, Ys, Zs).

Here's  a declarative reading of the code:

Clause 1:  Appending an empty list in front of a list equals that list.

Clause 2:  Appending [X|Xs] in front of a list equals the result of  appending
Xs in front of the list, and then putting X in front of that result.

This neatly avoids any recursion boggle for Basic etc. programmers.  Indeed, it doesn't even look like programming as they have known it.

After understanding the declarative reading they can then run traces of append's execution on various examples and more readily understand what is going on.


[...]

-- 
---------------------------
|  BBB                b    \    Barbara at LivingHistory stop co stop uk
|  B  B   aa     rrr  b     |
|  BBB   a  a   r     bbb   |   ,008015L080180,022036,029037
|  B  B  a  a   r     b  b  |   ,047045,L014114L4.
|  BBB    aa a  r     bbb   |
-----------------------------


Boris Vassilev

unread,
May 15, 2016, 4:19:56 AM5/15/16
to Fabrice Bizec, SWI-Prolog
Hello Fabrice,

few comments I hope you find helpful.

Trivial operations over sequences in most so called procedural languages are traditionally done with loop constructs, for example "for" or "while". Say you need to take a sequence S of letters and make a sequence T where each "a" in S is "b". In an imaginary language that looks like C++:

*S1*
==
for (int i = 0; i < S.length(); ++i) {
    if (S[i] == 'a') T[i] = 'b';
    else T[i] = S[i];
}

==

But there is a nicer way to do it even in a low-level, procedural language like C++.

*S2*
==
char tr(char c)
{
    if (c == 'a') return 'b';
    return c;
}

transform(S.begin(), S.end(), T.begin(), tr);
==

This is nicer mainly because I don't have to write a loop, think about loop invariants, indexing, etc.

Now: the Prolog recursive solution analogous to the "for" loop above would be maybe something like this:

*S3*
==
as_to_bs([], []).
as_to_bs([a|Xs], [b|Ys]) :-
    as_to_bs(Xs, Ys).
as_to_bs([X|Xs], [X|Ys]) :-
    dif(X, a),
    as_to_bs(Xs, Ys).
==

or, if you want to make it even more like the "for" loop above:

*S4*
==
as_to_bs([], []).
as_to_bs([X|Xs], [Y|Ys]) :-
    (   X == a
    ->  Y = b
    ;   Y = X
    ),
    as_to_bs(Xs, Ys).
==

At that point, everyone is screaming at me, "Y U NO maplist"

*S5*
==
as_to_bs(S, T) :-
    maplist(a_to_b, S, T).

a_to_b(X, Y) :-
    (   X == a
    ->  Y = b
    ;   Y = X
    ).
==

No explicit recursion any more: just like in the "transform" example above, we have replaced the trivial iteration over a sequence with a higher-order predicate.

Similarly, if I wanted to find the product of a list (of arithmetic expressions), I might do it like this, again without explicit recursion:

*S6*
==
list_product([X|Xs], P) :-
    foldl(product, Xs, X, P).

product(X, Y, P) :-
    P is X * Y.
==

Exercise: write list_product/2 without the help of a meta-predicate, with an explicit iteration over the list.

Open question: Do you need to know how to define the recursion explicitly in order to be able to appreciate the use of predicates like maplist and foldl?

Open question: What is the fundamental difference between the definitions in *S1* and *S4*?

We haven't even started talking about one of Prolog's main strengths: backtracking. Because a predicate can give multiple solutions, and because we can collect those solutions, there is a different way to avoid explicit iteration over lists. Using the built-in member/2 to enumerate the elements of a list using backtracking, the definition of a_to_b/2 from above, and findall/2 to collect the multiple solutions, directly from the top level:

*S7*
==
?- findall(Y, ( member(X, "banana"), a_to_b(X, Y) ), T).
T = [b, b, n, b, n, b].

==

If you already have a list, you would usually not use this indirection, but sometimes you don't have a list, but a predicate that has multiple solutions. You could for example define the following predicate:

*S8*
==
op(+).
op(-).
op(*).
op(/).

==

Now, you can use the univ operator, =../2, to create different expressions and evaluate them. Again, from the top level:

*S9*
==
?- op(Op), E =.. [Op, 2, 3], R is E.
Op =  (+), E = 2+3, R = 5 ;
Op =  (-), E = 2-3, R = -1 ;
Op =  (*), E = 2*3, R = 6 ;
Op =  (/), E = 2/3, R = 0.6666666666666666.

==

Now you are generating all possible solutions through backtracking. If you instead had a condition:

*S10*
==
?- op(Op), E =.. [Op, 2, 3], E =:= 5.
Op =  (+),
E = 2+3 ;
false.

==

Do you see where this is going?

Ok, let's dig into it a bit more. Let's define a predicate, expr/3, which makes an arithmetic expression out of 2 operands and one of the 4 available operators:

*S11*
==
expr(X, Y, E) :-
    op(Op),
    E =.. [Op, X, Y].
==

All that is left now is to enumerate possible expressions and test them:

*S12*
==
?- permutation([1,60,8,3], [X|Xs]),
   foldl(expr, Xs, X, E),
   E =:= 50.
X = 1,
Xs = [8, 3, 60],
E = 60- (3+ (8-1)) ;
X = 1,
Xs = [3, 8, 60],
E = 60- (8+ (3-1)) . % and so on

==

Again, I hope that you find this helpful.

Cheers,
Boris










Currently in the EEST time zone: This is UTC +3:00
Save our in-boxes! http://emailcharter.org

--
You received this message because you are subscribed to the Google Groups "SWI-Prolog" group.
To unsubscribe from this group and stop receiving emails from it, send an email to swi-prolog+...@googlegroups.com.
Visit this group at https://groups.google.com/group/swi-prolog.
For more options, visit https://groups.google.com/d/optout.

Boris Vassilev

unread,
May 15, 2016, 5:19:36 AM5/15/16
to Fabrice Bizec, SWI-Prolog
PS: Because I am afraid that I didn't say straight what the whole point of this email was.

I realize that none of what I said and showed is news to you. The message was that code is executed on a computer, but it is also written and read by people. For me personally the strongest selling point of Prolog is that it is possible to write reasonably efficient code that is quite readable by others. Most of the SWI-Prolog library code (at least the Prolog code) is a good example of this.

Cheers,
Boris



Currently in the EEST time zone: This is UTC +3:00
Save our in-boxes! http://emailcharter.org

Jorge G Forero

unread,
May 15, 2016, 7:37:51 AM5/15/16
to SWI-Prolog
Dear Fabrice, Barbara is right! Without recursion Prolog has no valid reason to exist. Fortunately i learnt and fall "in love" with Prolog because by tracing the append predicate i learnt "logic". Prof. James A. Bowen use this to illustrate what's all about. Thanks to him and now to Barbara to remind me. Good luck... Jorge

Fabrice Bizec

unread,
May 15, 2016, 10:23:45 AM5/15/16
to SWI-Prolog, fbi...@gmail.com
Hello Boris,


I didn't know the way you solve the problem :

op(+).
op(-).
op(*).
op(/).

expr(X, Y, E) :-
    op(Op),
    E =.. [Op, X, Y].
solve :-

   permutation([1,60,8,3], [X|Xs]),
   foldl(expr, Xs, X, E),
   E =:= 50,
   writeln(E).

Even a french scholar who wrote a book i read : "Prolog programmation par l'exemple" didn't mention it relating to that problem.

You may take the point of student learning recursion immediately to teach them right programing thinking but i know some developper engineer who don't know it because they don't come from computer engineer scholarship but from scientists (physics, biology) scholarship. 

Nevertheless, i think that the making of systems that avoid recursion and the decoupling of the delta of two terms for implementing rules from it's generalisation (with recursion by the 'solver') may be theorically interesting.

Sorry for my bad english,

Regards.

Julio Di Egidio

unread,
May 16, 2016, 7:18:44 AM5/16/16
to SWI-Prolog
On Sunday, May 15, 2016 at 3:22:54 AM UTC+2, barbara wrote:
 
Instead, I prefer to introduce Prolog via declarative readings of Prolog programs, which is something that will not remind them of Basic etc.

I am of the opposite advice: the *operational* semantics of Prolog is primary and should be taught primarily, because that is what a Prolog program actually does.

(As for the usual presumptions, these really prove that a programmer is a programmer, while a non-programmer does not even know what programming means.  And more could be said, about the lack of respect which is really a total lack of perspective, and so on.  Just poor students...)

Julio

Barb Knox

unread,
May 16, 2016, 5:22:09 PM5/16/16
to Julio Di Egidio, SWI-Prolog
On 16 May 2016, at 23:18, Julio Di Egidio <ju...@diegidio.name> wrote:

On Sunday, May 15, 2016 at 3:22:54 AM UTC+2, barbara wrote:
 
Instead, I prefer to introduce Prolog via declarative readings of Prolog programs, which is something that will not remind them of Basic etc.

I am of the opposite advice: the *operational* semantics of Prolog is primary and should be taught primarily, because that is what a Prolog program actually does.

Except, the correct operational semantics of Prolog is complicated, IMO vastly too complicated for a newbie.  When you introduce Prolog via an operational semantics do you really cover all of:  logical variables, the local stack, the heap, garbage collection, the choice stack, and the trail??  That would be massively too much and too foreign for a Prolog beginner.  So I assume you use a lot of handwaving to gloss over those items and others which make Prolog very different from Basic etc.

And what a program "actually does" is no more important than what it "actually means".


(As for the usual presumptions, these really prove that a programmer is a programmer, while a non-programmer does not even know what programming means.

So your definition of programming is purely procedural?  That's archaic (and I'm probably even older than you are, and have coded a lot in assembly and machine languages).

And more could be said, about the lack of respect which is really a total lack of perspective, and so on.

I'm lost.  Do you mean respect for procedurally?  If so, why is it deserving of such respect?  And perspective on what?  And so on what?  I would really like to know.

Just poor students...)

Probably not "just".


Julio

Markus Triska

unread,
May 16, 2016, 6:13:58 PM5/16/16
to SWI-Prolog, ju...@diegidio.name
Hi all,


On Monday, May 16, 2016 at 11:22:09 PM UTC+2, barbara wrote:

Except, the correct operational semantics of Prolog is complicated, IMO vastly too complicated for a newbie.

Barbara's statement hits the nail on the head. The precise operational semantics of Prolog are vastly too complicated to understand for beginners. And not only beginners! I can show dozens of examples where also very experienced Prolog programmers fail or have a very hard time to fully grasp the operational aspects of very modest programs. For example, go through the issue tracker of SWI-Prolog: You will find cases where several implementors discuss operational semantics in a thread with hundreds of messages. It is typical in such cases that the precise operations that lead to the problem are completely unclear for a long time, but the mistake is immediately obvious from the declarative properties that are violated.

Further, please all think the issue through more fully: What is it that a Prolog program actually does? To answer this to its ultimate extent, you need more knowledge than any human can realistically have and take more complexities into account than you can possibly understand. For example, what is the probability that your CPU works as intended? And even if the CPU were designed without flaws, which is extremely unlikely in itself, what is the probability that the computation is distorted by other events, such as solar eruptions? From such considerations, even if they do not make you outright reject the whole concept, you at least see that understanding "what it actually does" to its full extent is completely out of reach for humans.

The declarative semantics, on the other hand, can be explained and understood easily, and are basically reducible to a single language element that can be conveyed over a dinner.

All the best,
Markus

Jan Burse

unread,
May 16, 2016, 8:24:10 PM5/16/16
to SWI-Prolog, ju...@diegidio.name
Barnara wrote:
> Except, the correct operational semantics of Prolog is complicated, IMO vastly too complicated for a newbie. 

But the operational semantics and the declarative reading are two
sides of the same coin, and they coincidince in Prolog.

This is the beauty of Prolog. It holds for a great deal of Prolog levels
(pure Prolog, certain forms of Datalog, certain forms of negation as
failure, etc. etc.).

Pitty this insight got lost over the time. You find it in the original
DEC-10 Prolog user manual explicitly stated.

Here is a link: See Section

I.2. Declarative and Procedural Semantics

https://www.cs.cmu.edu/Groups/AI/util/lang/prolog/doc/intro/prolog.doc.

Its like as if you touch your head with your hand. And then
you look into a mirror and see yourself touching your head
with hand. What is real, what is not?

Bye

P.S.: Both views a fairly trivial, there are one page Haskell
programms that implement for example pure Prolog with
unification, could serve as material for operational semantics.

Declarative reading of pure Prolog is also not extremely difficult, 
if you understand the Hebrand domain, you have already payed
half of the bill.

But for the later you need a good math teacher for this and
not a CS teacher. CS teacher can't do it.

Jan Burse

unread,
May 16, 2016, 8:34:33 PM5/16/16
to SWI-Prolog
So in my opinion you need at least two dinners, and an
extremely good discussion partner.

Jan Wielemaker

unread,
May 17, 2016, 3:01:31 AM5/17/16
to Jan Burse, SWI-Prolog, ju...@diegidio.name
On 05/17/2016 02:24 AM, Jan Burse wrote:
>
> But the operational semantics and the declarative reading are two
> sides of the same coin, and they coincidince in Prolog.
>
> This is the beauty of Prolog. It holds for a great deal of Prolog levels
> (pure Prolog, certain forms of Datalog, certain forms of negation as
> failure, etc. etc.).
>
> Pitty this insight got lost over the time. You find it in the original
> DEC-10 Prolog user manual explicitly stated.

I don't agree with you that often, but this time I think I agree. If you
think only about the declarative reading you have IMO no longer a
_programming_ language. Use ASP. If you only look at the procedural
reading it can get pretty hard to understand. Prolog's procedural
reading can be used to implement _algorithms_ that can either implement
things that are not well solved by built-in inference engine as well as
to script purely declarative parts together to make them talk to the
world, etc.

Cheers --- Jan

Jan Burse

unread,
May 18, 2016, 7:09:42 AM5/18/16
to SWI-Prolog
BTW:
Still wondering where recursivity stems from.
The ethymological template example seems to be:

    active --> activity

But don't have yet a clear grip what should force me to
use the longer word(*). But we find it here and then:

   http://edu.epfl.ch/coursebook/en/godel-and-recursivity-MATH-483

   http://www.hec.unil.ch/logique/enseignement/recursivity

   http://blog.zhdk.ch/trans/rekursivitat/

But there is also back formation, the example being:

    active --> act

So we might want to simply write "The algorithm then recurses on
the children of the current tree node."

Which means "The algorithm then acts on the children of the current
tree node in the same way it already acted on the current tree node".

Right?

Bye

Jan Burse

unread,
May 18, 2016, 7:17:50 AM5/18/16
to SWI-Prolog
Fabrice Bizec wrote:
>
Nevertheless, i think that the making of systems that avoid recursion
> and the decoupling of the delta of two terms for implementing rules from
> it's generalisation (with recursion by the 'solver') may be theorically interesting.

Could you elaborate more on this? It looks that if your example is
solved via permutation and fold you have delegated recursion to
some existing predicates, in one case even non-deterministic recursion.

But your quote above says also something about examples and
generalization, which I don't quite understand?

Jan Burse

unread,
May 18, 2016, 7:51:23 AM5/18/16
to SWI-Prolog
You could make the following similar example. We could
for example define a prediate sort/2 as follows:

sort(X, Y) :-
    permutation(X, Y),
    sorted(Y).

But then there is a long way, in terms of finding the alterantive
solution and in terms of convincing oneself or others that the
alternative solution does the same, from the above to the following:

sort(X, Y) :-
     /* quick sort */

-- OR --

sort(X, Y) :-
    /* merge sort */

I am not sure that is possibly to build systems that only use
the functional specification, and derive automatically a
program that has also good non-functional properties, such
as memory usage and time usage.

Whereby I think its irrelevant whether the target code uses
REC or WHILE. For example you can code a great deal of
sorting algorithms without recursion, maybe even creating an
extra stack data structure to simulate recursion and not
pressuring the native stack.(*)

Bye

(*)
You find such code even in the SWI-Prolog source in many
places. Don't have links with me, but it is sometimes of advantage
to recode recursive stuff differently, also because of the cyclic
terms.

Fabrice Bizec

unread,
May 19, 2016, 2:22:32 AM5/19/16
to SWI-Prolog
Hello,


Yes it is delegation of recursion.

look :

% A knight want to kill a Dragoon which have 5 heads and 9 tails
% He can cut 1 or 2 heads or 1 or 2 tails
% When he cut 1 tail, 2 new tails appear
% When he cut 2 tails, 1 new head appear
% When he cut 1 head, 1 new head appear
% When he cut 2 heads, there is nothing new.
% How to kill the dragoon so he have no head and no tail anymore ?
% cut 1 queue => + 2 queues
cut(dragon(H, Q), dragon(H, NovoQ)) :-
   Q >= 1,
   NovoQ is Q + 1.
% cut 2 queues => + 1 head
cut(dragon(H, Q), dragon(NovoH, NovoQ)) :-
   Q >= 2,
   NovoQ is Q - 2,
   NovoH is H + 1.
% cut 2 heads
cut(dragon(H, Q), dragon(NovoH, Q)) :-
   H >= 2,
   NovoH is H - 2.
sword([ [dragon(H, Q)], HISTO], [ [dragon(NovoH, NovoQ)], [dragon(NovoH, NovoQ)|HISTO]]) :-
   cut(dragon(H, Q), dragon(NovoH, NovoQ)).
dragonKilled([dragon(0, 0)|_], _) :- !.
killDragon :-
   reset,
   solver(sword, dragonKilled, [dragon(5, 7)], [], HISTO),
   writeln(HISTO).

%
% SYSTEM PART THAT THE BASIC PROLOG PROGRAMMER SHOULD NOT SEE
%
use_module(library(gensym)).


isSolved(_, _, [], _) :- !, fail.
isSolved(P, Pargs, [[INLIST, HISTO]|_], HISTO) :-

 call(P, INLIST, Pargs).
isSolved(P, Pargs, [_|L], HISTO) :-
 isSolved(P, Pargs, L, HISTO).
purge(_, [], []).
purge(H, [[Lnums|Histo]|L], [[LnumsRes|Histo]|LRES]) :-
    sort(Lnums, LnumsRes),
    \+ histo(H, LnumsRes), !,
    asserta(histo(H, LnumsRes)),
    purge(H, L, LRES).
purge(H, [_|L], LRES) :-
    purge(H, L, LRES).
solverSub(_, _, [], []).
solverSub(H, GENE, [X|Lnodes], LRES) :-

 findall(FREE, call(GENE, X, FREE), LLRES),
 purge(H, LLRES, PurgeLLRES),
 solverSub(H, GENE, Lnodes, LINTER),
 append(PurgeLLRES, LINTER, LRES).

solver(GENE, SUCCESS, NODE_INIT, LargSuccess, HISTO):-
 dynamic(histo/2),
 dynamic(this/2),
 gensym(h, H),
 gensym(n, N),
 NODESinit = [[NODE_INIT, []]],
 asserta(this(N, NODESinit)),
 repeat,
 this(N, Lnodes),
 solverSub(H, GENE, Lnodes, LRES),
 retractall(this(N, _)),
 asserta(this(N, LRES)),
 isSolved(SUCCESS, LargSuccess, LRES, HISTO).
reset :-
 dynamic(histo/2),
 dynamic(this/2),
 retractall(histo(_, _)),
 retractall(this(_, _)).

Here, the predicate 'sword' make the 'delta' from an initial situation (S) to another (S prime) : it generates the nodes from a node of the search tree.
The predicate 'solver' make the generalization of 'sword' possible by searching concretely the solution : it build the search tree.
The predicate 'dragonKilled' check if the solution is found.

Markus Triska

unread,
May 19, 2016, 3:32:10 AM5/19/16
to SWI-Prolog
Hi Fabrice,

you are currently using a very imperative way to solve this task. This comes with many shortcomings. For instance, you cannot use this in all directions, i.e., you cannot use it to verify given solutions, complete partially instantiated solutions etc.

I show you a more declarative solution:

:- use_module(library(clpfd)).

move(dragon(H,T0), tail(1), dragon(H,T)) :- T #= T0 + 1.
move(dragon(H0,T0), tail(2), dragon(H,T)) :- H #= H0 + 1, T #= T0 - 2.
move(dragon(H,T), head(1), dragon(H,T)).
move(dragon(H0,T), head(2), dragon(H,T)) :- H #= H0 - 2.

initial_state(dragon(5,9)).

moves(Ms) :-
    initial_state(S0),
    length(Ms, _),
    phrase(moves(S0), Ms).


moves(dragon(0,0)) --> [].
moves(S0) --> [Move],
    { move(S0, Move, S) },
    moves(S).


Example query and its result:

?- moves(Ms).
Ms = [tail(1), tail(2), tail(2), tail(2), tail(2), tail(2), head(2), head(2), head(2), head(2), head(2)] .

Note that I am using Definite Clause Grammers (DCGs) to conveniently describe the list of moves. A move is a relation between two states: One before the move, and one after the move. Iterative deepening is used to find a shortest solution.

The solution is usable in all directions.

All the best!
Markus



Fabrice Bizec

unread,
May 19, 2016, 5:08:36 AM5/19/16
to SWI-Prolog
Hello, Markus,


The "imperative way" is only in the prolog part that the user shouldn't see.

Your grammar use recursion ans my goal was to avoid it except in the 'solver engine' part.

Regards

Markus Triska

unread,
May 19, 2016, 6:24:21 AM5/19/16
to SWI-Prolog
Hi Fabrice,



Your grammar use recursion ans my goal was to avoid it except in the 'solver engine' part.

In my solution, the grammar is the 'solver engine' part.

So yes, our solutions both use recursion only in the 'solver engine' part.

All the best,
Markus

Boris Vassilev

unread,
May 19, 2016, 6:42:46 AM5/19/16
to SWI-Prolog
Hello Fabrice,

you should notice that there is a single predicate that is defined recursively, and this is the Definite Clause Grammar (DCG) rule moves//1. Because move/3 is a non-deterministic predicate (has up to four solutions), moves//1 in practice defines a 4-way tree with possible dragons. Because of how backtracking works, evaluating phrase(moves(S0), Ms) does (an implicitly defined) depth-first search of this tree.

Not immediately obvious, but the trick here is using length(Ms, _). This will generate lists with increasing lengths, and thus trees with increasing depth will be searched. This is an "iterative deepening" approach to solving: you search the tree depth-first (Prolog's proof strategy), but the trees increase in depth on each iteration.

A different approach would be to do a breadth-first search of the tree. For this, you usually need a queue for the nodes of the tree that need to be looked at next.

Either way, it is important that the "recursion" that you talk about is in the definition of the search tree, and not in the definition of the search strategy.

Cheers,
Boris

PS: As it currently stands, Markus's solution allows you to have a dragon (not a dragoon!) with a negative number of heads or tails. The solution he shows is an example of that. You would need to add the appropriate checks at the beginning of each body of move/3, for example T #>= 1 and so on.

Currently in the EEST time zone: This is UTC +3:00
Save our in-boxes! http://emailcharter.org

--

Jan Burse

unread,
May 19, 2016, 7:09:55 AM5/19/16
to SWI-Prolog
Nice:
https://de.wikipedia.org/wiki/Hydra_%28Mythologie%29#/media/File:Hercules_slaying_the_Hydra.jpg

Little bit similar to the collatz sequence:
http://stackoverflow.com/questions/30026151/uneven-tabling-performance-in-bprolog-8-1

Can we combine tabling and CLP(FD) in general? Can we combine
tabling and CLP(FD) in this example? Or could we do something with
tabling and without CLP(FD) here?

Julio Di Egidio

unread,
May 25, 2016, 1:04:29 PM5/25/16
to swi-p...@googlegroups.com
On Monday, May 16, 2016 at 11:22:09 PM UTC+2, barbara wrote:
On 16 May 2016, at 23:18, Julio Di Egidio <ju...@diegidio.name> wrote:

On Sunday, May 15, 2016 at 3:22:54 AM UTC+2, barbara wrote:
 
Instead, I prefer to introduce Prolog via declarative readings of Prolog programs, which is something that will not remind them of Basic etc.

I am of the opposite advice: the *operational* semantics of Prolog is primary and should be taught primarily, because that is what a Prolog program actually does.
Except, the correct operational semantics of Prolog is complicated, IMO vastly too complicated for a newbie.  When you introduce Prolog via an operational semantics do you really cover all of:  logical variables, the local stack, the heap, garbage collection, the choice stack, and the trail??  That would be massively too much and too foreign for a Prolog beginner.  So I assume you use a lot of handwaving to gloss over those items and others which make Prolog very different from Basic etc.

Are you serious?  One should rather conclude that you do not know what the operational semantics of Prolog is: it's unification and backtracking (SLD resolution), i.e. pretty much, at a more practical level, what the execution trace would show.  So, after the basics on facts and rules, you rather go on and explain list append...

Incidentally: there is *no need* for any of the implementation details you mention unless one is truly hacking low-level: e.g. in SWI a correct use of an nb_link_val, etc.  Definitely unneeded not only in a basic course, but really in 99.99% of the programs.

Incidentally #2: it is wrong that the denotational semantics is equivalent to the operational one as some here seem to believe, they are *not equivalent*, indeed the operational semantics is more restrictive: to begin with, not all programs that have a valid denotational semantics will terminate.  And I am not even an expert on these matters, nor I feel like digging the obvious out for you, but that is the ABC: the semantics of Prolog are not only explained in pretty much any decent book on the language (not on Wikipedia, where I see most articles are exactly as wrong as you -and Markus- IMO are on this matter), the semantics are even explicitly specified in the ISO standard...

And what a program "actually does" is no more important than what it "actually means".

Nope, what a program means *is* what a program does!

      (As for the usual presumptions, these really prove that a programmer is a programmer, while a non-programmer does not even know what programming means.

So your definition of programming is purely procedural?  That's archaic (and I'm probably even older than you are, and have coded a lot in assembly and machine languages).

You also keep conflating operational with procedural: so, on a side, do look up what the operational semantics of Prolog actually is, on the other side, it is also worth mentioning that procedural is not even technically meaningful: what you have in mind and keep demeaning (and for inconsistent reasons) is called *imperative*.

HTH, your students.  (EOD.)

Julio

Barb Knox

unread,
May 26, 2016, 12:40:16 AM5/26/16
to Julio Di Egidio, SWI-Prolog
On 26 May 2016, at 05:04, Julio Di Egidio <ju...@diegidio.name> wrote:

On Monday, May 16, 2016 at 11:22:09 PM UTC+2, barbara wrote:
On 16 May 2016, at 23:18, Julio Di Egidio <ju...@diegidio.name> wrote:

On Sunday, May 15, 2016 at 3:22:54 AM UTC+2, barbara wrote:
 
Instead, I prefer to introduce Prolog via declarative readings of Prolog programs, which is something that will not remind them of Basic etc.

I am of the opposite advice: the *operational* semantics of Prolog is primary and should be taught primarily, because that is what a Prolog program actually does.

Except, the correct operational semantics of Prolog is complicated, IMO vastly too complicated for a newbie.  
When you introduce Prolog via an operational semantics do you really cover all of:  logical variables, the local stack, the heap, garbage collection, the choice stack, and the trail??  That would be massively too much and too foreign for a Prolog beginner.  So I assume you use a lot of handwaving to gloss over those items and others which make Prolog very different from Basic etc.

Are you serious?  One should rather conclude that you do not know what the operational semantics of Prolog is: it's unification and backtracking (SLD resolution), i.e. pretty much, at a more practical level, what the execution trace would show.  So, after the basics on facts and rules, you rather go on and explain list append...

There is more along those lines that a first course treating Prolog semantics would probably cover, such as
!, ->, \+, and throw / catch.

Incidentally: there is *no need* for any of the implementation details you mention unless one is truly hacking low-level: e.g. in SWI a correct use of an nb_link_val, etc.  Definitely unneeded not only in a basic course, but really in 99.99% of the programs.

Fair point.  I was concentrating on the fully correct operational semantics, not just the parts of it that would be useful for a beginner.  My bad.

Incidentally #2: it is wrong that the denotational semantics is equivalent to the operational one as some here seem to believe, they are *not equivalent*, indeed the operational semantics is more restrictice: to begin with, not all programs that have a valid denotational semantics will terminate.  And I am not even an expert on these matters not I feel like digging the obvious out for you, but that is the ABC: the semantics of Prolog are not only explained in pretty much any decent book on the language (not on Wikipedia, where I see most articles are exactly as wrong as you and Markus IMO are on this matter),

the semantics are even explicitly specified in the ISO standard...

One should surely not inflict ISO standards documents on beginners. ☺︎

And what a program "actually does" is no more important than what it "actually means".

Nope, what a program does *is* what a program means.

I disagree.  A program is expected to implement some specification.  Most of most specifications is declarative.  Having a declarative meaning for a program text facilitates seeing if it meets its specification.  Absent that, one is often limited to running tests, which as we know can show that a program fails some of its specification, but cannot show that it meets all of it.

      (As for the usual presumptions, these really prove that a programmer is a programmer, while a non-programmer does not even know what programming means.

(What are these "usual presumptions"?  And isn't a Real Programmer rather like a True Scotsman?)

So your definition of programming is purely procedural?  That's archaic (and I'm probably even older than you are, and have coded a lot in assembly and machine languages).

You also keep conflating operational with procedural: so, on a side, do look up what the operational semantics of Prolog actually is, on the other side, it is also worth mentioning that procedural is not even technically meaningful: what you have in mind and keep demeaning (and for inconsistent reasons) is called *imperative*.

"Procedural" and "imperative" are usually synonyms.  For example, see
<http://stackoverflow.com/questions/1619834/difference-between-declarative-and-procedural-programming>.  (Google gives about 100,000 hits for  procedural declarative  and about 75,000 for imperative declarative .)

And I only demean procedural descriptions when there is a better alternative.  One very nice thing about Prolog is that there often is a better alternative.

And BTW, where have I been inconsistent?


HTH, your students.  (EOD.)

Eve of Destruction?  ☺︎  <https://www.allacronyms.com/EOD/Eve_of_Destruction>
Reply all
Reply to author
Forward
0 new messages