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

Joy (programming language) interpreter in Prolog

1,650 views
Skip to first unread message

Simon Forman

unread,
Aug 16, 2018, 5:55:06 PM8/16/18
to
This is a draft, and incomplete, but I wanted to share it a little early.

Joy is a purely-functional, stack-based, "concatinative" language. Juxtaposition of names denotes composition of functions.

https://en.wikipedia.org/wiki/Joy_(programming_language)

http://www.kevinalbrecht.com/code/joy-mirror/joy.html


This mostly works, but there are some issues:
- I haven't implemented all the functions and combinators.
- It parses and passes numbers but the clp(fd) math only works with ints.
- The "compiler" doesn't work with loop or loop constructs (while).


Example evaluation:

?- joy(`0 [3 2 1] [+] step`, [], So).
So = [6] ;
false.



%
% Copyright © 2018 Simon Forman
%
% This file is part of Thun
%
% Thun is free software: you can redistribute it and/or modify
% it under the terms of the GNU General Public License as published by
% the Free Software Foundation, either version 3 of the License, or
% (at your option) any later version.
%
% Thun is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU General Public License
% along with Thun. If not see <http://www.gnu.org/licenses/>.
%
:- use_module(library(clpfd)).
:- use_module(library(dcg/basics)).
:- op(990, xfy, ≡). % for Joy definitions.

/*
An entry point.
*/

joy(InputString, StackIn, StackOut) :-
phrase(joy_parse(Expression), InputString), !,
thun(Expression, StackIn, StackOut).

/*
Parser
*/

joy_parse([T|S]) --> blanks, joy_term(T), blanks, joy_parse(S).
joy_parse([]) --> [].

joy_term(N) --> number(N), !.
joy_term(S) --> "[", !, joy_parse(S), "]".
joy_term(A) --> chars(Chars), !, {atom_string(A, Chars)}.

chars([Ch|Rest]) --> char(Ch), chars(Rest).
chars([Ch]) --> char(Ch).

char(Ch) --> [Ch], {Ch \== 91, Ch \== 93, code_type(Ch, graph)}.
% Why not "]" or ']' or `]`? Why 93?

/*
Interpreter
thun(Expression, InputStack, OutputStack)
*/

thun([], S, S).
thun( [Lit|E], Si, So) :- literal(Lit), !, thun(E, [Lit|Si], So).
thun( [Func|E], Si, So) :- func(Func, Si, S), thun(E, S, So).
thun([Combo|E], Si, So) :- combo(Combo, Si, S, E, Eo), thun(Eo, S, So).

/*
Literals
*/

literal(V) :- var(V).
literal(I) :- number(I).
literal([]).
literal([_|_]).
literal(true).
literal(false).

/*
Functions
*/

func(app1, [P, Xi|S], [Xo|S]) :- thun(P, [Xi|S], [Xo|_]).
func(app2, [P, Xi, Yi|S], [Xo, Yo|S]) :- thun(P, [Xi|S], [Xo|_]), thun(P, [Yi|S], [Yo|_]).

func(cons, [A, B|S], [[B|A]|S]).
func(swap, [A, B|S], [B, A|S]).
func(dup, [A|S], [A, A|S]).
func(pop, [_|S], S ).
func(+, [A, B|S], [C|S]) :- C #= A + B.
func(-, [A, B|S], [C|S]) :- C #= B - A.
func(*, [A, B|S], [C|S]) :- C #= A * B.
func(/, [A, B|S], [C|S]) :- C #= B div A.

func(nullary, [P|S], [X|S]) :- thun(P, S, [X|_]). % Combinator.
func(infra, [P, R|S], [Q|S]) :- thun(P, R, Q). % Combinator.

func(concat, [A, B|S], [C|S]) :- append(B, A, C).
func(flatten, [A|S], [B|S]) :- flatten(A, B).
func(swaack, [R|S], [S|R]).
func(stack, S , [S|S]).
func(clear, _ , []).
func(first, [[X|_]|S], [X|S]).
func(rest, [[_|X]|S], [X|S]).
func(unit, [X|S], [[X]|S]).

func(rolldown, [A, B, C|S], [B, C, A|S]).
func(dupd, [A, B|S], [A, B, B|S]).
func(over, [A, B|S], [B, A, B|S]).
func(tuck, [A, B|S], [A, B, A|S]).

func(rollup, Si, So) :- func(rolldown, So, Si).
func(uncons, Si, So) :- func(cons, So, Si).

func(>, [A, B|S], [T|S]) :- B #> A #<==> R, r_truth(R, T).
func(<, [A, B|S], [T|S]) :- B #< A #<==> R, r_truth(R, T).
func(=, [A, B|S], [T|S]) :- B #= A #<==> R, r_truth(R, T).
func(>=, [A, B|S], [T|S]) :- B #>= A #<==> R, r_truth(R, T).
func(<=, [A, B|S], [T|S]) :- B #=< A #<==> R, r_truth(R, T).
func(<>, [A, B|S], [T|S]) :- B #\= A #<==> R, r_truth(R, T).

/*
Definitions
*/

func(Name, Si, So) :- Name ≡ Body, thun(Body, Si, So).

swons ≡ [swap, cons].
unswons ≡ [uncons, swap].
x ≡ [dup, i].
b ≡ [[i], dip, i].
sqr ≡ [dup, *].
ifte ≡ [[nullary], dipd, swap, branch].
while ≡ [swap, [nullary], cons, dup, dipd, concat, loop].
popop ≡ [pop, pop].
ccons ≡ [cons, cons].
unary ≡ [nullary, popd].
binary ≡ [unary, popd].
trinary ≡ [binary, popd].
popd ≡ [[pop], dip].
popdd ≡ [[pop], dipd].
popopd ≡ [[popop], dip].
popopdd ≡ [[popop], dipd].
dupd ≡ [[dup], dip].
dupdd ≡ [[dup], dipd].
second ≡ [rest, first].
third ≡ [rest, second].
fourth ≡ [rest, third].
rrest ≡ [rest, rest].
unit ≡ [[], cons].
drop ≡ [[rest], times].
at ≡ [drop, first].
of ≡ [swap, at].
sum ≡ [0, swap, [+], step].
product ≡ [1, swap, [*], step].
size ≡ [0, swap, [pop, 1, +], step].
fork ≡ [[i], app2].
cleave ≡ [fork, [popd], dip].
codireco ≡ [cons, dip, rest, cons].
make_generator ≡ [[codireco], ccons].

r_truth(0, false).
r_truth(1, true).

/*
Combinators
*/

combo(i, [P|S], S, Ei, Eo) :- append(P, Ei, Eo).
combo(dip, [P, X|S], S, Ei, Eo) :- append(P, [X|Ei], Eo).
combo(dipd, [P, X, Y|S], S, Ei, Eo) :- append(P, [Y, X|Ei], Eo).

combo(branch, [T, _, true|S], S, Ei, Eo) :- append(T, Ei, Eo).
combo(branch, [_, F, false|S], S, Ei, Eo) :- append(F, Ei, Eo).

combo(loop, [_, false|S], S, E, E ).
combo(loop, [B, true|S], S, Ei, Eo) :- append(B, [B, loop|Ei], Eo).

combo(step, [_, []|S], S, E, E ).
combo(step, [P, [X]|S], [X|S], Ei, Eo) :- !, append(P, Ei, Eo).
combo(step, [P, [X|Z]|S], [X|S], Ei, Eo) :- append(P, [Z, P, step|Ei], Eo).

combo(times, [_, 0|S], S, E, E ).
combo(times, [P, 1|S], S, Ei, Eo) :- append(P, Ei, Eo).
combo(times, [P, N|S], S, Ei, Eo) :- N #>= 2, M #= N - 1, append(P, [M, P, times|Ei], Eo).
combo(times, [_, N|S], S, _, _ ) :- N #< 0, fail.


/*
Compiler
*/

joy_compile(Name, Expression) :- jcmpl(Name, Expression, Rule), asserta(Rule).

show_joy_compile(Name, Expression) :- jcmpl(Name, Expression, Rule), write(Rule).

jcmpl(Name, Expression, Head :- Body) :-
call_residue_vars(thun(Expression, Si, So), Term),
copy_term(Term, Term, Gs),
Head =.. [func, Name, Si, So],
thrp(Gs, Body).

thrp([A,B], (A, B)) :- !.
thrp([A|B], (A, C)) :- thrp(B, C).
thrp([A], A).

j4n bur53

unread,
Aug 16, 2018, 9:49:48 PM8/16/18
to
If you want to upload code, and at the same
time have an easy way to do changes and even
see diffs, I recommend gist.

Its free of charge and from GitHub. Very
simple to use, and you could post links to
gist, instead long code snippets here,

which are difficult to deal with. gists
can be also cloned by other users.

https://gist.github.com/

Simon Forman schrieb:

j4n bur53

unread,
Aug 16, 2018, 9:55:10 PM8/16/18
to
I wrote my gist recommendation, because
you wrote: "This is a draft, and incomplete,
but I wanted to share ..."

I am pretty much convinced the additional
benefit of gist/GitHub is the revision tab,
it makes practically changes

self explanatory.

j4n bur53 schrieb:

Simon Forman

unread,
Aug 17, 2018, 10:42:44 AM8/17/18
to
On Thursday, August 16, 2018 at 6:55:10 PM UTC-7, j4n bur53 wrote:
> I wrote my gist recommendation, because
> you wrote: "This is a draft, and incomplete,
> but I wanted to share ..."
>
> I am pretty much convinced the additional
> benefit of gist/GitHub is the revision tab,
> it makes practically changes self explanatory.
>

I appreciate the advice, I don't mean to flood the list with a bunch of code. I've got the newbie willies from Prolog and I might be acting a bit silly.


I've used GitHub in the past but I'm moving away from them now. (The contradiction between developing free software on a closed proprietary system became too much for me. I moved to the Open Source Development Network https://osdn.net/ for Joy/Thun and that has worked well, but it doesn't support a gist-like feature (yet.) Interestingly, light of my recent conversion to Prolog, they are based in Japan, home of the Fifth Generation Computer...)

In lieu of GitHub what do you think of SWISH? This is a Sudoku solution I came up with https://swish.swi-prolog.org/p/Boring%20Sudoku.swinb is this a convenient way to share code snippets?

Thanks again,
warm regards,
~Simon

Markus Triska

unread,
Aug 17, 2018, 12:44:00 PM8/17/18
to
Hi Simon,

Simon Forman <forman...@gmail.com> writes:

> This is a draft, and incomplete, but I wanted to share it a little
> early.

This is great, thank you for sharing it!

The first question I asked the program is: Which Joy programs are there?

?- length(Es, _), thun(Es, Is, Os).
Es = [],
Is = Os ;
Es = [_8842],
Os = [_8842|Is] ;
Es = [_8842, _8848],
Os = [_8848, _8842|Is] ;
Es = [_8842, _8848, _8854],
Os = [_8854, _8848, _8842|Is] ;
Es = [_8842, _8848, _8854, _8860],
Os = [_8860, _8854, _8848, _8842|Is] .

That's not the whole story, is it?

A clean representation lets us fairly enumerate all cases:

literal(lit(_)).
literal(int(_)).
literal([]).
literal([_|_]).
literal(true).
literal(false).

I am using the wrappers int/1 and lit/1 to symbolically distinguish the
cases. This lets us make the program much more general. Sample query:

?- length(Expr, _), thun(Expr, Is, Os).
Expr = [],
Is = Os ;
Expr = [lit(_5236)],
Os = [lit(_5236)|Is] ;
Expr = [int(_5236)],
Os = [int(_5236)|Is] ;
Expr = [[]],
Os = [[]|Is] ;
Expr = [[_5236|_5238]],
Os = [[_5236|_5238]|Is] ;
Expr = [true],
Os = [true|Is] .

The same with thrp/2. I asked: Which cases are there at all?

?- thrp(Ls, Goal).
Ls = [_5642, _5648],
Goal = (_5642, _5648).

So I went on and instead defined:

conjunction(A, G, (G,A)).

Hence, we get:

?- foldl(conjunction, Ls, true, Goal).
Ls = [],
Goal = true ;
Ls = [_8040],
Goal = (true, _8040) ;
Ls = [_8040, _8052],
Goal = ((true, _8040), _8052) ;
Ls = [_8040, _8052, _8064],
Goal = (((true, _8040), _8052), _8064) .

Regarding the "]" question, you can use 0']:

?- X = 0'].
X = 93.

Arguably even better though is to use:

:- set_prolog_flag(double_quotes, chars).

which entails:

?- Ls = "]".
Ls = [']'].

and yields more readable results than codes.

In Emacs, I used M-h align-regexp RET ≡ RET to get a nice indentation:

swons ≡ [swap, cons].
unswons ≡ [uncons, swap].
x ≡ [dup, i].
b ≡ [[i], dip, i].
sqr ≡ [dup, *].
ifte ≡ [[nullary], dipd, swap, branch].
etc.

I hope this helps, and please keep up the great work!

Thank you and all the best,
Markus


--
comp.lang.prolog FAQ: http://www.logic.at/prolog/faq/
The Power of Prolog: https://www.metalevel.at/prolog

Simon Forman

unread,
Aug 17, 2018, 8:26:30 PM8/17/18
to
On Friday, August 17, 2018 at 9:44:00 AM UTC-7, Markus Triska wrote:

>
> This is great, thank you for sharing it!

Thank you, I really appreciate your encouragement. Your "Power of Prolog" has been a huge help and inspiration. And CLP(FD) is so great!
I made (just) the change you indicate and I get:


?- length(Expr, _), thun(Expr, Is, Os).
Expr = [],
Is = Os ;
Expr = [lit(_788)],
Os = [lit(_788)|Is] ;
Expr = [lit(_794), lit(_804)],
Os = [lit(_804), lit(_794)|Is] ;
Expr = [lit(_800), lit(_810), lit(_820)],
Os = [lit(_820), lit(_810), lit(_800)|Is]


What am I doing wrong? Is there a change to be made to thun?


> The same with thrp/2. I asked: Which cases are there at all?
>
> ?- thrp(Ls, Goal).
> Ls = [_5642, _5648],
> Goal = (_5642, _5648).
>
> So I went on and instead defined:
>
> conjunction(A, G, (G,A)).
>
> Hence, we get:
>
> ?- foldl(conjunction, Ls, true, Goal).
> Ls = [],
> Goal = true ;
> Ls = [_8040],
> Goal = (true, _8040) ;
> Ls = [_8040, _8052],
> Goal = ((true, _8040), _8052) ;
> Ls = [_8040, _8052, _8064],
> Goal = (((true, _8040), _8052), _8064) .

With thrp (sorry about the name, it's onomatopoeic but silly) I wanted to exclude the empty list. I changed the definition to:


thrp([A], A).
thrp([A|B], (A, C)) :- thrp(B, C).


?- thrp(Who, What).
Who = [What] ;
Who = [_626, _634],
What = (_626, _634) ;
Who = [_626, _638, _646],
What = (_626, _638, _646) ;
Who = [_626, _638, _650, _658],
What = (_626, _638, _650, _658) ;
Who = [_626, _638, _650, _662, _670],
What = (_626, _638, _650, _662, _670) .


> Regarding the "]" question, you can use 0']:
>
> ?- X = 0'].
> X = 93.
>
> Arguably even better though is to use:
>
> :- set_prolog_flag(double_quotes, chars).
>
> which entails:
>
> ?- Ls = "]".
> Ls = [']'].
>
> and yields more readable results than codes.

Awesome, thanks. I'll try that. I'm still getting used to Prolog's treatment of strings.

> In Emacs, I used M-h align-regexp RET ≡ RET to get a nice indentation:
>
> swons ≡ [swap, cons].
> unswons ≡ [uncons, swap].
> x ≡ [dup, i].
> b ≡ [[i], dip, i].
> sqr ≡ [dup, *].
> ifte ≡ [[nullary], dipd, swap, branch].
> etc.

I'm torn between aligned and ragged styles. If the spacing is too great with the aligned format it breaks the horizontal continuity, but the ragged style is ragged. I also can't decide between putting them in alphabetical order vs some kind of grouping of similar functions.

> I hope this helps, and please keep up the great work!

This is a great help, thank you again. I don't know if you recall the solution to the Zebra puzzle I made after reading your chapter on puzzles last year ( https://gist.github.com/calroc/603ed919bc814ccee10c1b3df6142fec ) but your work has had a big (if delayed) influence on me. So, in a way, this code is your doing as well as mine. :-)

I have to say, I feel really foolish for not catching on sooner. I have a copy of "The Art of Prolog" but it wasn't on my desk, or even the shelf. I had to go dig it out of a box in storage last week. Lo and behold, there's a reprise of Warren 1980 right there in Ch. 24 (in section IV "Applications" which is kind of a victory lap after they've laid out a treasure chest, a cornucopia of wonders in the preceding pages.)

It was Warren's paper on compilers in Prolog that finally kicked me into gear. I knew I wanted to use e.g. Prolog or Kanren to do "advanced" modelling of stack effects (type inference), but I was resigned to writing a compiler (to Python) in Python. I was in the midst of that when I saw Warren's paper.

Now there's an implementation of Joy in Prolog already, written by von Thun (I can't find it online, it's in the archive made available by his University https://www.latrobe.edu.au/__data/assets/file/0007/240298/Joy-Programming.zip ) so I used that and "Power of Prolog" to reimplement the basics of Joy, just to see what it would be like. It was only when I reimplemented the type inferencer in Prolog and realized that it was just another version of the interpreter code that I really began to see the light.

I've been unconscionably foolish not to use Prolog sooner. I mean, I've been working as a professional developer for years now. People have paid me good money. Mostly for Python code. Now I come to find out I've been wasting unbelievable, ridiculous amounts of time and energy. It's crazy. My only consolation is that I'm not alone, it appears that most of the industry is stuck in a steampunk era of computing. Especially now that the machines are so fast and huge.

I'm pretty excited to use Prolog, and now I have a Joy interpreter embedded in it to express anything that might be too awkward in the Logical Paradigm, and with a little bit of work I can get assembly language out of it as needed.

Thanks again for your help and encouragement, and for the "Power of Prolog"!
Warm regards,
~Simon

Markus Triska

unread,
Aug 18, 2018, 6:08:23 AM8/18/18
to
Hi Simon,

thank you for your kind words!

Simon Forman <forman...@gmail.com> writes:

> Is there a change to be made to thun?

Yes, I changed the second clause of thun/3 from:

thun( [Lit|E], Si, So) :- literal(Lit), !, thun(E, [Lit|Si], So).

to:

thun( [Lit|E], Si, So) :- literal(Lit), thun(E, [Lit|Si], So).

to prevent the predicate from prematurely committing to only one of
several possibilities, and to generate all answers for general cases. Of
course, other changes are also necessary: For example, the parser must
generate this clean representation, and the compiler must also take it
into account.

> thrp([A], A).
> thrp([A|B], (A, C)) :- thrp(B, C).

Personally, I think that it would be perfectly adequate to compile the
code to a list of goals Gs, and then to emit maplist(call, Gs) as the
single goal for each predicate that is generated. For example, let's
forget about thrp/2 entirely for a moment and write instead:

jcmpl(Name, Expression, Head :- maplist(call, Gs)) :-
call_residue_vars(thun(Expression, Si, So), Term),
copy_term(Term, Term, Gs),
Head =.. [func, Name, Si, So].

We then get:

?- joy_compile(to_the_fifth, [dup, dup, *, dup, *, *]).
true ;
false.

?- listing(func(to_the_fifth, _, _)).
:- dynamic func/3.

func(to_the_fifth, [B|A], [C|A]) :-
maplist(call,

[ clpfd:(D*B#=C),
clpfd:(D in 0..sup),
clpfd:(E^2#=D),
clpfd:(E in 0..sup),
clpfd:(B^2#=E)
]).
func(to_the_fifth, B, C) :-
to_the_fifth≡A,
thun(A, B, C).

true.

and quite frankly, I find it reasonable to expect the underlying Prolog
system to compile this to more efficient inline-calls, i.e., to compile
away the maplist/2 for us. Such an improvement has the potential to
affect many more user programs, and would simplify your code too.

If you want to exclude the empty list, you can add the constraint
dif(Gs, []) or Gs = [_|_], to jcmpl/3, for which func_expr_clause/3 is
probably a more telling name. However, must empty lists of goals indeed
never arise?

>> I hope this helps, and please keep up the great work!
>
> This is a great help, thank you again. I don't know if you recall the
> solution to the Zebra puzzle I made after reading your chapter on
> puzzles last year (
> https://gist.github.com/calroc/603ed919bc814ccee10c1b3df6142fec ) but
> your work has had a big (if delayed) influence on me. So, in a way,
> this code is your doing as well as mine. :-)

Yes, I remember: Your solution was, and still is, very beautiful! Thank
you for posting this back then.

> I have to say, I feel really foolish for not catching on sooner. I
> have a copy of "The Art of Prolog" but it wasn't on my desk, or even
> the shelf. I had to go dig it out of a box in storage last week. Lo
> and behold, there's a reprise of Warren 1980 right there in Ch. 24 (in
> section IV "Applications" which is kind of a victory lap after they've
> laid out a treasure chest, a cornucopia of wonders in the preceding
> pages.)

"The Art of Prolog" is full of wonder and delight, I highly recommend
this book, and also "The Craft of Prolog" by Richard O'Keefe.

If it is any consolation: You may now feel "foolish for not catching on
sooner", yet you are already now starting with Prolog. From there, this
feeling will never go away, and if anything, it will likely get even
worse. Take Richard O'Keefe for example, one of the world's foremost
Prolog experts with decades of experience. In "The Practice of Prolog",
he discusses a technique and then states that he wished he had
discovered it years ago. I have heard similar statements from almost all
leading Prolog experts about specific techniques. So, in a few years,
you will likely similarly regret not having used or invented a
particular Prolog technique years earlier. This is a sign of progress.

> I've been unconscionably foolish not to use Prolog sooner. I mean,
> I've been working as a professional developer for years now. People
> have paid me good money. Mostly for Python code. Now I come to find
> out I've been wasting unbelievable, ridiculous amounts of time and
> energy. It's crazy. My only consolation is that I'm not alone, it
> appears that most of the industry is stuck in a steampunk era of
> computing. Especially now that the machines are so fast and huge.

In John Gustafson's book "The End of Error", there is an analogy I often
think about:

In 1970, a printer might produce something that looks like this, and
take about 30 seconds to do so: [picture]

Over forty years later, a laser printer still might take 30 seconds
to put out a single page, but technology has improved to allow
full-color, high-resolution output.

What we are currently doing, in important areas of computing such as
numerical calculations, is the equivalent of printing thousands of
low-quality pages per second, instead of getting a single high-quality
page in 30 seconds.

A few paragraphs later, the book states:

Eventually it becomes so obvious that change is necessary that a
wrenching shift finally takes place. Such a shift is overdue for
numerical computing, where we are stuck with antediluvian tools.
Once we make the shift, it will become possible to solve problems
that have baffled us for decades. The evidence supporting that claim
is here in this book, which contains quite a few results that appear
to be new.

https://www.crcpress.com/The-End-of-Error-Unum-Computing/Gustafson/p/book/9781482239867

In my opinion, a similar shift is overdue for programming languages, and
I hope we witness it in our lifetimes. And if not, let's at least do
what we can to make it happen later.

All the best,

burs...@gmail.com

unread,
Aug 18, 2018, 8:59:35 AM8/18/18
to
Hi Simon, Hi Markus,

Can you use Joy to find solutions to the
Golumb Ruler problem? See also:

Modeling and Solving AI Problems in Picat
http://ktiml.mff.cuni.cz/~bartak/AAAI2017/slides.pdf

Here is a solution without the hassel of a new
language like Picat, we already have Log-Nonsense-Talk,
no need for more nonsense like Picat-Meow-Meh:

Golomb ruler in B-Prolog.
http://www.csplib.org/Problems/prob006/models/golomb_ruler_bp.pl.html

Can this be done in SWI-Prolog CLP(FD) as well,
or in Joy? It uses array index, SWI-Prolog CLP(FD)
doesn't have array index, right?

burs...@gmail.com

unread,
Aug 18, 2018, 9:02:45 AM8/18/18
to
I think in the B-Prolog version, X[I] was
short-cut for nth1(I,X).

Simon Forman

unread,
Aug 18, 2018, 5:33:18 PM8/18/18
to
On Saturday, August 18, 2018 at 3:08:23 AM UTC-7, Markus Triska wrote:
> Yes, I changed the second clause of thun/3 from:
>
> thun( [Lit|E], Si, So) :- literal(Lit), !, thun(E, [Lit|Si], So).
>
> to:
>
> thun( [Lit|E], Si, So) :- literal(Lit), thun(E, [Lit|Si], So).
>
> to prevent the predicate from prematurely committing to only one of
> several possibilities, and to generate all answers for general cases. Of
> course, other changes are also necessary: For example, the parser must
> generate this clean representation, and the compiler must also take it
> into account.

Ah, that makes sense. I appreciate your taking the time to spell out what must seem so obvious. Thanks. :)



> > thrp([A], A).
> > thrp([A|B], (A, C)) :- thrp(B, C).
>
> Personally, I think that it would be perfectly adequate to compile the
> code to a list of goals Gs, and then to emit maplist(call, Gs) as the
> single goal for each predicate that is generated. For example, let's
> forget about thrp/2 entirely for a moment and write instead:
>
> jcmpl(Name, Expression, Head :- maplist(call, Gs)) :-
> call_residue_vars(thun(Expression, Si, So), Term),
> copy_term(Term, Term, Gs),
> Head =.. [func, Name, Si, So].

That makes sense. I've been holding off on the meta-programming predicates for now, although I had my eye on maplist for implementing map in Joy, but this is exactly what I would have done if I had the confidence. Instead I used what I had already learned to hack it with that thrp/2 relation.

> We then get:
>
> ?- joy_compile(to_the_fifth, [dup, dup, *, dup, *, *]).
> true ;
> false.
>
> ?- listing(func(to_the_fifth, _, _)).
> :- dynamic func/3.
>
> func(to_the_fifth, [B|A], [C|A]) :-
> maplist(call,
>
> [ clpfd:(D*B#=C),
> clpfd:(D in 0..sup),
> clpfd:(E^2#=D),
> clpfd:(E in 0..sup),
> clpfd:(B^2#=E)
> ]).
> func(to_the_fifth, B, C) :-
> to_the_fifth≡A,
> thun(A, B, C).
>
> true.
>
> and quite frankly, I find it reasonable to expect the underlying Prolog
> system to compile this to more efficient inline-calls, i.e., to compile
> away the maplist/2 for us. Such an improvement has the potential to
> affect many more user programs, and would simplify your code too.

Yes, I agree, and I'm going to adopt this version. I was experimenting with partial evaluation/deduction and folding/unfolding and I can't see any barrier to inlining it, eh?

That reminds me that I have to look into profiling and timing Prolog code. Any tips there? (I haven't even skimmed the relevant sections of the SWI-PL manual yet, so RTFM is a fine response.) ;)


> If you want to exclude the empty list, you can add the constraint
> dif(Gs, []) or Gs = [_|_], to jcmpl/3, for which func_expr_clause/3 is
> probably a more telling name. However, must empty lists of goals indeed
> never arise?

Now that you mention it, it's perfectly legitimate to compile functions that are completely defined by their stack effect alone, without additional terms.

?- show_joy_compile(over, [swap, dup, [swap], dip]).
false.

by adding a rule:

thrp([], true).

This now works.

?- show_joy_compile(over, [swap, dup, [swap], dip]).
func(over,[_686,_692|_694],[_692,_686,_692|_694]):-true
true .

Is that a decent solution or should I modify func_expr_clause/3 to be more precise about it's third argument?


> > I have to say, I feel really foolish for not catching on sooner. I
> > have a copy of "The Art of Prolog" but it wasn't on my desk, or even
> > the shelf. I had to go dig it out of a box in storage last week. Lo
> > and behold, there's a reprise of Warren 1980 right there in Ch. 24 (in
> > section IV "Applications" which is kind of a victory lap after they've
> > laid out a treasure chest, a cornucopia of wonders in the preceding
> > pages.)
>
> "The Art of Prolog" is full of wonder and delight, I highly recommend
> this book, and also "The Craft of Prolog" by Richard O'Keefe.
>
> If it is any consolation: You may now feel "foolish for not catching on
> sooner", yet you are already now starting with Prolog. From there, this
> feeling will never go away, and if anything, it will likely get even
> worse. Take Richard O'Keefe for example, one of the world's foremost
> Prolog experts with decades of experience. In "The Practice of Prolog",
> he discusses a technique and then states that he wished he had
> discovered it years ago. I have heard similar statements from almost all
> leading Prolog experts about specific techniques. So, in a few years,
> you will likely similarly regret not having used or invented a
> particular Prolog technique years earlier. This is a sign of progress.

I agree with you, but in my case a friend of mine tried to "read me in" to Prolog about twenty years ago. The thing that bothers me the most is that, looking back, I can't identify a factor or reason that prevented me from getting it sooner. I'm not actually stupid, and I have a strong commitment to finding and using the best tool for the job, or so I thought. I'm a technophile. Yet I was oblivious. It's like a foodie who doesn't realize cheese is edible. The reason this bothers me so much is that I would like to clue in others, yet I can't understand how to do it, because I can't understand the nature of my own apathy.

What I'm getting at is: It's illogical to NOT use Prolog, programmers are logical people, why don't more programmers use Prolog? An why doesn't my own conversion experience give me more data to answer that question?
Yes, exactly! All of the above.

My interest in Joy originally stemmed from a desire to find a vehicle for Dr. Margaret Hamilton's "Higher Order Software" methodology that developed out of the Apollo 11 mission to the Moon. Dr Hamilton identified the sources of error in the software development process and designed a system that eliminated them. In modern terms the system worked by permitting only provably-correct modifications to what amounts to an AST structure, as opposed to editing text files. It didn't catch on, to say the least, but it provides a method for developing bug-free software.

That's why I'm interested in Joy, and that's why Warren's paper on compilers written in Prolog caught my eye and pushed me over the lip of the energy well to really learn it. I see a short, wide road to provably-correct software development using Joy and Prolog to compactly represent software down-to-the-metal.

I think the next step for me is to implement a compiler for a simple processor (Prof. Wirth's RISC for the Oberon Project most likely, it's simple yet formidable enough to run the Oberon OS and emulators have been written for it in many languages including C and JavaScript.) Then I have to figure out how to compile Joy constructs to ASM structures, it's not quite like a typical language but there is a lot of existing research around e.g. compiling Forth that I can draw on. The other thing to do would be compiling the Prolog version of Joy and just saying "That's the thing there." meaning the resulting binary is what I would call the Joy program, even though it's just a Prolog program pretending to be Joy.

Warm regards, and have a good weekend,
~Simon

Simon Forman

unread,
Aug 18, 2018, 5:37:21 PM8/18/18
to
On Saturday, August 18, 2018 at 5:59:35 AM UTC-7, burs...@gmail.com wrote:
> Hi Simon, Hi Markus,
>
> Can you use Joy to find solutions to the
> Golumb Ruler problem? See also:

Yes, but I'm afraid it would just be a table of the known optimal solutions

https://en.wikipedia.org/wiki/Golomb_ruler#Known_optimal_Golomb_rulers


The article also says that something called "distributed.net" is working on the larger ones, so there's little point.

In any event, it seems to me to be a very Prolog-shaped problem. I doubt the Joy solution would be as concise or insightful as a solution in the Logical Paradigm.

Cheers,
~Simon


burs...@gmail.com

unread,
Aug 18, 2018, 9:26:41 PM8/18/18
to
How about something co-inductive?

lazlib.joy -- "lazy" infinite and finite lists
laztst.joy -- test file
laztst.out -- output

https://github.com/xieyuheng/joy

burs...@gmail.com

unread,
Aug 18, 2018, 9:37:24 PM8/18/18
to
How different is your Joy implementation from
pico-Joy? Does it have a special name your Joy
implementation?

The pico-Joy literal handling seems to be
straight forward:

/* literals */
exe(true , (S, true.S)) .
exe(false , (S, false.S)) .
exe([] , (S, [].S)) .
exe(L1.L , (S, (L1.L).S)) .
exe(I , (S, I.S)) :-
integer(I) .

They evaluate to them selves, and they are
some booleans true/false, lists, and integers.
The lists are not further type checked.

I guess when the literats respectively the
data contains lists, a lot of things can
be done, like the lazy stuff.

You need of course also some ops for the
data. He has for example:

exe(cons , (L.L1.S, (L1.L).S)) .
exe(null , ([].S, true.S)) :-
! .
exe(null , (X.S, false.S)) .
exe(uncons , ((L1.L).S, L.L1.S)) .

Source, Manfred von Thun:

PicoJoy - a tiniest Joy-in-Prolog
I call this thing PicoJoy because it is a
cut-down version of what I used to call MicroJoy .
Any experienced Prolog writer should be able to
extend it. It runs under MU-Prolog (from Melbourne
University), and probably under any other
standard Prolog.

https://github.com/xieyuheng/joy/blob/master/html/j-pico-prolog.html

burs...@gmail.com

unread,
Aug 18, 2018, 10:36:11 PM8/18/18
to
Ok, I see, was scrolling back:
https://groups.google.com/d/msg/comp.lang.prolog/X0ujdV9ML5U/AU0UFMZ7EAAJ

You allow variables as literals. Is
this something from the object level,
or rather the meta level?

Can you make a typical example with
a variable literal? For example markus
triska suggested literal(lit(_)),

not sure whether this works if variables
were from the meta level. Probably you
would need iterative deepening

if you want to get something out of
meta variables...

Markus Triska

unread,
Aug 19, 2018, 6:35:36 AM8/19/18
to
Hi Simon,

Simon Forman <forman...@gmail.com> writes:

> That reminds me that I have to look into profiling and timing Prolog
> code. Any tips there? (I haven't even skimmed the relevant sections of
> the SWI-PL manual yet, so RTFM is a fine response.) ;)

One quite portable building block I like for timing is:

goal_time(Goal, T) :-
statistics(runtime, [T0|_]),
Goal,
statistics(runtime, [T1|_]),
T #= T1 - T0.

Let us use this to compare the (presumed!) speedup you get with
conjunctions over maplist/2:

n_speedup(N, F) :-
length(Ls, N),
maplist(=(true), Ls),
foldl(conjunction, Ls, true, G),
goal_time(maplist(call, Ls), T1),
goal_time(time(G), T2),
F is T1/T2.

where conjunction/3 is defined as conjunction(A, G, (G,A)).

For the first few thousand N, I can barely measure the speedup, because
T2 is 0 so often.

However, with some luck, I get for example:

?- n_speedup(10 000, F).
%@ % 1 inferences, 0.001 CPU in 0.001 seconds (90% CPU, 1389 Lips)
%@ F = 3.

and further (note that maplist/2 is much faster in this case!):

?- n_speedup(20 000, F).
%@ % 2 inferences, 0.007 CPU in 0.010 seconds (71% CPU, 282 Lips)
%@ F = 0.3333333333333333.

For N #>= 50 000, I get a segmentation fault. I have filed this as:

https://github.com/SWI-Prolog/swipl-devel/issues/327

For the moment, let us work around this by defining conjunction/3
instead as:

conjunction(A, G, (A,G)).

with which we get for example:

?- n_speedup(100 000, F).
%@ % 1 inferences, 0.019 CPU in 0.022 seconds (86% CPU, 52 Lips)
%@ F = 1.263157894736842.

All considered, these results seem to suggest that this difference will
likely not be the most performance-critical part of your program. The
difference will vanish entirely if you for example augment SWI-Prolog's
library(apply_macros) with inlining functionality for maplist/2, which
would potentially benefit many other programs too.

> like a foodie who doesn't realize cheese is edible. The reason this
> bothers me so much is that I would like to clue in others, yet I can't
> understand how to do it, because I can't understand the nature of my
> own apathy.

Joe Armstrong's slides on Erlang contain several lessons about this:

http://www.cse.chalmers.se/~rjmh/Armstrong/bits.ps

One quote from these slides I often think about is:

"To displace an existing technology you have to wait for something
to fail"

Currently, many problems we are working on are still comparatively
trivial, and - with extraordinary effort - we can often solve them also
with tools whose inadequacy borders on comicality.

As I see it, working on Prolog now is to prepare everything in advance
so that we can meet an as of yet unprecedented demand for better methods
that will arise in the future.

A personal anecdote that is related to this point:

One of my friends used to work in the area of medical recommender
systems. He once told me that the company's chief programmer was working
on an editor for their own domain-specific language, and that the editor
was still extremely unreliable: It used to crash and get the
highlighting wrong. Later that day, I sent him Emacs definitions that he
could use instead: The syntax highlighting worked reliably, and it was
clear that the indenting was useful enough as a starting point. It had
taken me only a few hours to put together these Emacs definitions.

My friend told me that he cannot show this idea at the company for
social reasons: It would have made the chief programmer look
incompetent, because he had been working on their custom, unreliable,
editor during the past 3 years, and he was not considered strong enough
to let go of so much wasted effort.

Other than that, the interpreter you posted also requires features that
have been available in SWI-Prolog for less than 10 years. My impression
is that you are perfectly in time.

j4n bur53

unread,
Aug 19, 2018, 8:05:03 AM8/19/18
to
Markus Triska schrieb:
> For N #>= 50 000, I get a segmentation fault. I have filed this as:
>
> https://github.com/SWI-Prolog/swipl-devel/issues/327

I guess its a problem of body conversion and call. The
naked goal crashes the system. One factor could be the
way you build the goal. Usually a goal has the form
(a,(b,(c,..))), but you build it,

(((..,c),b),a), call this the second form. My system
expects that the first form is more common and has
special tail recursion, so that it also crashed in
in the less common second form:

java.lang.StackOverflowError
at jekpro.model.molec.EngineWrap.countGoal(EngineWrap.java:57)
at jekpro.model.molec.EngineWrap.countGoal(EngineWrap.java:62)

Yes, that could be the same problem in SWI-Prolog:

Simon Forman

unread,
Aug 19, 2018, 10:54:07 PM8/19/18
to
On Saturday, August 18, 2018 at 6:37:24 PM UTC-7, j4n bur53 wrote:
> How different is your Joy implementation from
> pico-Joy? Does it have a special name your Joy
> implementation?

I was using picojoy as a guide when I wrote my version, I think the major difference is that I'm using some more modern/recent features?

Simon Forman

unread,
Aug 19, 2018, 11:05:28 PM8/19/18
to
On Sunday, August 19, 2018 at 3:35:36 AM UTC-7, Markus Triska wrote:
> Hi Simon,
>
> Simon Forman <...> writes:
>
> > That reminds me that I have to look into profiling and timing Prolog
> > code. Any tips there? (I haven't even skimmed the relevant sections of
> > the SWI-PL manual yet, so RTFM is a fine response.) ;)
>
> One quite portable building block I like for timing is:
>
> goal_time(Goal, T) :-
> statistics(runtime, [T0|_]),
> Goal,
> statistics(runtime, [T1|_]),
> T #= T1 - T0.

Awesome! Thanks. Another door opens...
Oh but I hope no expression would have thousands of constraints, or am I just being timid?

In any event, I don't imagine the compiler as a performance bottleneck. It would make sense to run it offline to pre-compile definitions to a source file, or even machine code.

The maplist code does seem nicer:

name_expr_rule(Name, Expression, Rule) :-
call_residue_vars(thun(Expression, Si, So), Term),
copy_term(Term, Term, Gs),
Head =.. [func, Name, Si, So],
rule(Head, Gs, Rule).

rule(Head, [], Head ).
rule(Head, [A|B], Head :- maplist(call, [A|B])).



Is it weird that there's not already a list-to-commas relation in the "stdlib"? Am I the first person to try to do this? Is maplist just the solution and I'm skittish due to inexperience?


> > like a foodie who doesn't realize cheese is edible. The reason this
> > bothers me so much is that I would like to clue in others, yet I can't
> > understand how to do it, because I can't understand the nature of my
> > own apathy.
>
> Joe Armstrong's slides on Erlang contain several lessons about this:
>
> http://www.cse.chalmers.se/~rjmh/Armstrong/bits.ps
>
> One quote from these slides I often think about is:
>
> "To displace an existing technology you have to wait for something
> to fail"
>
> Currently, many problems we are working on are still comparatively
> trivial, and - with extraordinary effort - we can often solve them also
> with tools whose inadequacy borders on comicality.
>
> As I see it, working on Prolog now is to prepare everything in advance
> so that we can meet an as of yet unprecedented demand for better methods
> that will arise in the future.

I'm impressed with your far-reaching vision. And certainly in my specific case you're practically prophetic. I hope that demand arises sooner rather than later. :)

> A personal anecdote that is related to this point:
>
> One of my friends used to work in the area of medical recommender
> systems. He once told me that the company's chief programmer was working
> on an editor for their own domain-specific language, and that the editor
> was still extremely unreliable: It used to crash and get the
> highlighting wrong. Later that day, I sent him Emacs definitions that he
> could use instead: The syntax highlighting worked reliably, and it was
> clear that the indenting was useful enough as a starting point. It had
> taken me only a few hours to put together these Emacs definitions.
>
> My friend told me that he cannot show this idea at the company for
> social reasons: It would have made the chief programmer look
> incompetent, because he had been working on their custom, unreliable,
> editor during the past 3 years, and he was not considered strong enough
> to let go of so much wasted effort.

That's so brutal, like something out of Kafka. There's really nothing constructive I can say about that. Heh.

> Other than that, the interpreter you posted also requires features that
> have been available in SWI-Prolog for less than 10 years. My impression
> is that you are perfectly in time.

Cheers! It feels that way. I really hope this thing turns out to be as useful as I think it might.

Warm regards,
~Simon

Simon Forman

unread,
Aug 19, 2018, 11:31:21 PM8/19/18
to
On Saturday, August 18, 2018 at 7:36:11 PM UTC-7, j4n bur53 wrote:
> Ok, I see, was scrolling back:
> https://groups.google.com/d/msg/comp.lang.prolog/X0ujdV9ML5U/AU0UFMZ7EAAJ
>
> You allow variables as literals. Is
> this something from the object level,
> or rather the meta level?

Actually, I haven't tried putting variable on the stack yet. Resolution has called them into being when required. Now there is a lot of meta-programming on Joy code as a matter of course, so I can't be sure that something I've done so far has caused the thun/3 relation to operate on an expression that has variables already on it. Maybe, maybe not.

> Can you make a typical example with
> a variable literal? For example markus
> triska suggested literal(lit(_)),
>
> not sure whether this works if variables
> were from the meta level. Probably you
> would need iterative deepening

The interesting thing is that Joy doesn't have variables, it's purely "point-free" and never names any arguments whatsoever.

I've done thing like, in the Python-based interpreter, putting Sympy variables (objects that represent symbolic variables) onto the stack and then run e.g. the quadratic formula over them (as a Joy expression) and then the resulting objects on the stack are Sympy expression objects that represent the two roots, rather than the numeric results. I haven't posted that online yet though... Here's the Quadratic formula in Joy FWIW: https://joypy.osdn.io/notebooks/Quadratic.html

(As an aside, it makes me so rueful to look at my few-weeks-old Python code for type inference and compiling. Just so much trash now... Look. I had this working:

e = (names(), (dup, (dup, (mul, (dup, (mul, (mul, ())))))))

print compile_yinyang('to_the_fifth_power', e)

def to_the_fifth_power(stack):
(a44, stack) = stack
a45 = mul(a44, a44)
a46 = mul(a45, a45)
a47 = mul(a46, a44)
stack = (a47, stack)
return stack


Compare:

?- show_joy_compile(to_the_fifth, [dup, dup, *, dup, *, *]).

func(to_the_fifth,[_7360|_7266],[_8784|_7266]):-maplist(call,[clpfd:(_8088*_7360#=_8784),clpfd:(_8088 in 0..sup),clpfd:(_7442^2#=_8088),clpfd:(_7442 in 0..sup),clpfd:(_7360^2#=_7442)])


A week of fiddly bug-prone work in Python. Two pages of code not including my own hand-rolled unification function.

Five lines of flawless Prolog that took as much time to write as type.

The only delay was not being able to discover call_residue_vars/2 and copy_term/3 on my own, and I had to convince myself to dig up my old gmail login to ask on here about it. (Google wouldn't let me subscribe with my non-gmail account, sad-face.)

Oh, there was also a delay associated with me not realizing right away that running a Joy expression in Prolog always returned the necessary information to implement the expression as it's own Prolog definition. It took me some time to realize that I was already done (once I knew the call_residue_vars+copy_term incantation!)

Yes, it makes me have some feels alright to look at that old Python code. I just have to shake my head ruefully.)


> if you want to get something out of
> meta variables...


I haven't even tried to think about the possibilities of exposing Prolog "primitives" in the Joy level.

I have a whole prototype UI that's meant to present a simple "super-calculator" interface to the user, and now I can include Logical Paradigm "magic" tricks as well...

Cheers, and warm regards,
~Simon

burs...@gmail.com

unread,
Aug 20, 2018, 1:28:31 AM8/20/18
to
Anything inductively defined can have variables,
for example on the meta level. Thats why I
asked, what your Prolog variables in literal

mean. I didn't imply that Joy as a programming
languages has variables on the object level, except
the function name definitions via ==,

if you allow function names to also be called
variables. But as soon as you model something
with Prolog respectively logic programming you

get variables into it. You don't need to have some
newer features used, just that mere fact that you
model something *declaratively* implies that you

get variables. Here is an example:

append([], X, X).
append([X|Y], Z, [X|T]) :- append(Y, Z, T).

You can call it ground:

?- append([1],[2,3],X).
X = [1,2,3]

Or you can call it non-ground in a backward way:

?-

Can your Joy interpreter do the same? Can
you define an append? What happens if you try
to ran it backwards, from a result to figure

out the arguments on the stack?

P.S.: I guess pico-joy cannot be run backwards
since it has some cuts in the wrong place.
But it should be not extremly difficult to

eliminate this cuts and get a pure Prolog
implementation, which can be run backwards.
Maybe with the help of iterative deepening.

P.P.S.: Maybe it was not so wise to jump
onto the new features of Prolog such as CLP(FD),
and not exploring *declarativity* itself,

at lest in my opinion CLP(FD) can only
increase declarativity, if the inductive
definitions are already declarative enough,

like no cuts, and the CLP(FD) might still
need some help, like replacing the Prolog
interpreter search strategy by interative

deepening or somesuch. Only if you combine
the both you might really get something out
of such an exercise. The exercise is not part

of the usual CLP(FD) exercises, where just
some code is hirarchically invoked to generate
a model. Here the Joy interpreter defines

inductively an evaluation, which needs additional
methods than only CLP(FD). These additional
methods are well known...

burs...@gmail.com

unread,
Aug 20, 2018, 1:30:55 AM8/20/18
to
Oops, forgot to paste what you get here:

Or you can call it non-ground in a backward way:

?- append(X,Y,[1,2,3]).
X = [],
Y = [1,2,3] ;
X = [1],
Y = [2,3] ;
X = [1,2],
Y = [3] ;
X = [1,2,3],
Y = []

burs...@gmail.com

unread,
Aug 20, 2018, 2:07:22 AM8/20/18
to
Pico-Joy after a small update, runs on Jekejeke Prolog:

Jekejeke Prolog 3, Runtime Library 1.3.0
(c) 1985-2018, XLOG Technologies GmbH, Switzerland

?- ensure_loaded('file:/Projects/Jekejeke/Prototyping/experiment/other/prolog2/bigmess/joylang/joy2.p').
% 1 consults and 0 unloads in 23 ms.
Yes

?- picojoy.
picojoy version 00.00
j: [[1],[2,3],concat].
[[1,2,3]]
j: stop.
Yes

Do you think we can run it backwards?

Source code and screenshot is here:
https://gist.github.com/jburse/116ee53cde5d98544cde5aa8b27e712e#file-joy2-p

I only did the following changes:
- No more singleton warnings
- Use \+ instead of not
- Use [_|_] instead of _._
- Do flush_output after prompt

So I did not yet eliminate the cuts and make
it fully declarative. But for "concat" I see
its not realized with cuts.

So I guess we can run it backwards?

BTW: The exelist of Pico-Joy has a simple DCG
reading, if instead of the pairs (X,Y) we would
simply use two arguments:

exelist([]) --> [].
exelist([R1|R]) -->
exe(R1),
exelist(R).

I retained the DCG-ish solution from the original
Pico-Joy interpreter and didn't introduce some
append/3 in the realization,

but maybe I should get rid of the pairs (X,Y),
would make it more compact and efficient.

burs...@gmail.com

unread,
Aug 20, 2018, 2:27:02 AM8/20/18
to
Ok, here is the answer, whether it can be
run backwards and whether it has variables.
The answer is has of course automaticall Prolog
variables, but there seems to be some problems,

see for yourself:

Jekejeke Prolog 3, Runtime Library 1.3.0
(c) 1985-2018, XLOG Technologies GmbH, Switzerland

?- list(X), list(Y), exelist([X,Y,concat], ([],[[1,2,3]])).
X = [],
Y = [1,2,3] ;
X = [1,2,3],
Y = [] ;
Error: Execution aborted since memory threshold exceeded.

Thats quite strange. I used the following type guard:

list(X) :- var(X), !, freeze(X, list(X)).
list([]).
list([_|X]) :- list(X).

It does not show the solutions [1],[2,3] and
[1,2],[3], and it does not terminate.
Will massage the code a little bit when I have
time, eliminate the cuts, maybe improve the guard

and maybe use another search strategy.

You see already problems *without* CLP(FD) that
need first to be solved and that cannot be
solved by CLP(FD). No numbers involved, was
*only* looking at some list processing.

BTW: I get the same result in SWI-Prolog, so
I guess there is no bug in my freeze or somesuch.

Welcome to SWI-Prolog (threaded, 64 bits, version 7.7.1)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.

?- list(X), list(Y), exelist([X,Y,concat], ([],[[1,2,3]])).
X = [],
Y = [1, 2, 3]
X = [1, 2, 3],
Y = []
ERROR: Out of global stack

Simon Forman

unread,
Aug 20, 2018, 5:20:38 PM8/20/18
to
I did some little experiments with the thun/3 relation to see if it could generate little expressions given some inputs and outputs and/or partial expressions. It mostly didn't work, with the same sort of out-of-stack problems and what-not.

I'm content with what it's capable of so far, but I know there will come a time soon when I want to explore program generation a little more. I'm still getting used to the idea that the compiler is mostly done!

My issues now are mostly mundane: Do I hook up a Tcl/Tk GUI through Python or make a web server? Should I write a lower-level compiler to some kind of ASM or C, or should I make a Joy-to-Factor translator and leverage Factor-lang's multiplatform native compiler? It's good, and Factor is almost Joy already so it shouldn't be difficult. Or is that all more "working too hard" and I should explore compiling the Prolog code with e.g. GNU Prolog compiler or something?

The only really interesting thing to do on the interpreter is figure out how to correctly compile loops without going into infinite recursion. I have to un-reify the loop construct at "compile-time" somehow, I think.

Cheers,
~S

burs...@gmail.com

unread,
Aug 20, 2018, 7:34:01 PM8/20/18
to
Mayb the backward reasoning would work, if we
would use a different type guard:

intlist(X) :- var(X), !, freeze(X, intlist(X)).
intlist([]).
intlist([Y|X]) :- int(Y), intlist(X).

int(Y) :- var(Y), !, feeze(Y, int(Y)).
int(Y) :- integer(Y).

I don't know whether Python has a freeze. Python
is not a logic programming language, but it might
still have something, although possibly without

hooking into unification. But unification makes it
especially interesting for Joy. The small step
semantics is only unification based pattern matching.

Ken is very well versed in LISP I guess, and who also
did O-Prolog, managed to provide aome freeze for his
Prolog. At least this example works:

| ?- freeze(X, (write(hello), nl)), X=a.
hello
X = a
yes

But I tried the list, and there is something wrong
in O-Prolog, I will post in the O-Prolog thread.

burs...@gmail.com

unread,
Aug 26, 2018, 9:37:00 PM8/26/18
to
Hi Simon,

You wrote "but the clp(fd) math only works
with ints". As the name FD says its finite
domains. So it only works with finite subsets

of ints, and you also need to use labeling.
I find neither finite subsets nor labeling
in your code. Probably the Example: Collatz

conjecture in Power of Prolog leads to some
missconception what CLP(FD) does. When you
dont do labeling, you can even not be sure

that your constraints are satisfiable, here
is an example (no labeling, no guarantee
of satisfiability):

?- [F,G] ins 0..1, F #= 1 #==> G #= 0, G #= 0 #==> F #= 0,
F #= 0 #==> G #= 1, G #= 1 #==> F #= 1.
F in 0..1,
F#=1#<==>_7160,
F#=0#<==>_7184,
F#=0#<==>_7208,
F#=1#<==>_7232,
_7160 in 0..1,
_7278#==>_7160,
_7278 in 0..1,
G#=1#<==>_7278,
G in 0..1,
G#=1#<==>_7370,
G#=0#<==>_7394,
G#=0#<==>_7418,
_7370 in 0..1,
_7184#==>_7370,
_7184 in 0..1,
_7394 in 0..1,
_7394#==>_7208,
_7208 in 0..1,
_7418 in 0..1,
_7232#==>_7418,
_7232 in 0..1.

?- [F,G] ins 0..1, F #= 1 #==> G #= 0, G #= 0 #==> F #= 0,
F #= 0 #==> G #= 1, G #= 1 #==> F #= 1, label([F,G]).
false.

Sorry for the spoiler.

Have Fun!

burs...@gmail.com

unread,
Aug 26, 2018, 9:45:58 PM8/26/18
to
Basically the following claim, by Markus Triska
here, is charlatan and selling snake oil:

"answers look like in general"
https://www.metalevel.at/prolog/concepts

Thats exactly what is not working with CLP(FD),
although it looks as if would work for

small examples.

burs...@gmail.com

unread,
Aug 26, 2018, 9:50:27 PM8/26/18
to
And its a pitty that Ulrich Neumerkel the ISO
convenor, via his if_/3 nonsense has joind
this humbug and shenanigan. At least we find
a honorable mention "more efficiently with if_/3."

What do you want to do more efficiently?
General answer nobody knows whether they
have values where they would succeeded, or
whether they would fail for all values?

burs...@gmail.com

unread,
Aug 26, 2018, 10:03:54 PM8/26/18
to
You see in normal circumstances for CLP(FD)
it is always used with finite domains and
some labeling. I guess it is the solve

statement in Picat. For example in this example:

"'Are you the one?' problem in Picat.
According to Wikipedia, "Are You The One?"
is a reality TV show produced by MTV, in which
a group of men and women are secretly paired
into male-female couples via a matchmaking
algorithm. Then, while living together, the
contestants try to identify all of these
"perfect matches.""
Hakan Kjellerstrand, 26.08.2018
http://hakank.org/picat/are_you_the_one.pi

Writing a pamphlet with the name "Power of Prolog"
and having readers that read this pamphlet,
doesn't change the fact, that non-finite

domains or omitting labeling, has sever
limitations. Its not what CLP(FD) was made
for it. And even if a CLP(Z) would be invented,

it would still have these severe limitations.
Just check out any universities course on
recursion theory.

burs...@gmail.com

unread,
Aug 27, 2018, 7:59:23 AM8/27/18
to
Hi,

Well you might even need assistance of a math
institute. It is not that Kolgomorov Complexity
or Gödels Incompletness Theorem would not

be connected to the issue at hand. But concerning
integers the problem is especially famous
under the heading of Hilberts 10-th Problem:

https://en.wikipedia.org/wiki/Hilbert's_tenth_problem

So even without a recursive Joy program,
just by virtue of integer diophantine equations,
you can get non-decidability.

Have Fun!

Simon Forman

unread,
Aug 28, 2018, 12:32:45 AM8/28/18
to
You gotta remember that the thun relation et. al. was only my second Prolog program ever. It's draft and written by a total newbie.

Thanks for pointing out that I'm using the CLP(FD) stuff wrong, I appreciate that. I'm leaning now towards just building "AST" and handling the actual evaluation later. I.e.:

func(+, [A, B|S], [add(A, B)|S]).
func(-, [A, B|S], [sub(B, A)|S]).
func(*, [A, B|S], [mul(A, B)|S]).
func(/, [A, B|S], [div(B, A)|S]).

func(>, [A, B|S], [lt(A, B)|S]).
func(<, [A, B|S], [gt(A, B)|S]).


Eventually I want to be able to emit machine code, or LLVM Intermediate Representation, for Joy definitions. There is a lot of existing material on compiling with Prolog and Forth, which is similar enough to Joy that a lot of it maps right over.) But all that to say that I'm not expecting to run the Joy interpreter in Prolog (even compiled Prolog) necessarily, rather to use the Prolog version to help define (and compile) proven-correct code.

As far as Algorithmic Information theory and "meta-biology" goes, my next step I think is to write a kind of "meta-grammar" that can generate other grammars and that has probabilities attached to each meta-rule that are adjusted according to how much each one participates in generating "fit" grammars (that generate "fit" strings.) I have the "advantage" of being relatively mathematically unsophisticated, I'm just clever enough to get the ball rolling, I hope.

Cheers,
~Simon
0 new messages