This question starts from Mat's answer to Algorithm improvement for enumerating binary trees which has only one input value that determines the number of all nodes for the binary tree, and the need to be able to have two input values with one being the number of unary nodes and the other being the number of binary nodes.
While I was able to derive a solution by using listing/1 and threading extra state variables:
e(t, B, B, U, U).
e(u(E), B0, B1, [_|U0], U1) :-
e(E, B0, B1, U0, U1).
e(b(E0, E1), [_|B0], B2, U0, U2) :-
e(E0, B0, B1, U0, U1),
e(E1, B1, B2, U1, U2).
e(U,B,Es) :-
length(Bs, B),
length(Us, U),
e(Es,Bs,[],Us,[]).
Note: See Prolog output below.
I was not satisfied with the use of length/2 as a constraint in that it is not obvious in it's use and that it was not using DCG. From previous other attempts at other problems I knew using numbers as a constraint would fail, e.g.
e_a(t, B, B, U, U).
e_a(u(E), B0, B1, U0, U2) :-
U1 is U0 + 1,
e_a(E, B0, B1, U1, U2).
e_a(b(E0, E1), B0, B3, U0, U2) :-
B1 is B0 + 1,
e_a(E0, B1, B2, U0, U1),
e_a(E1, B2, B3, U1, U2).
e_a(U,B,Es) :-
U =:= Us, % Arguments are not sufficiently instantiated 1=:=_2692
B =:= Bs,
e_a(Es,0,Bs,0,Us).
?- e_a(1,2,Es).
However upon searching I found the use of CLP(FD) with DCG, and decided to try that.
:-use_module(library(clpfd)).
e_b(t, B, B, U, U).
e_b(u(E), B0, B1, U0, U2) :-
U1 #= U0 + 1,
e_b(E, B0, B1, U1, U2).
e_b(b(E0, E1), B0, B3, U0, U2) :-
B1 #= B0 + 1,
e_b(E0, B1, B2, U0, U1),
e_b(E1, B2, B3, U1, U2).
e_b(U,B,Es) :-
U #=< Us,
B #=< Bs,
e_b(Es,0,Bs,0,Us).
?- e_b(1,2,Es).
however that results in an infinite loop returning no results.
Note: I understand the concepts of CLP(FD) but my practical use with it is next to none.
So the questions are:
- Can CLP(FD) be used with this solution and if so how?
- How would I convert the non DCG solution back into a DCG version?
Supplement
Starting code and listing
e(number) --> [].
e(u(Arg)) --> [_], e(Arg).
e(b(Left,Right)) --> [_,_], e(Left), e(Right).
?- listing(e).
e(t, A, A).
e(u(A), [_|B], C) :-
e(A, B, C).
e(b(A, C), [_, _|B], E) :-
e(A, B, D),
e(C, D, E).
Prolog output
?- e(1,2,Es).
Es = u(b(t, b(t, t))) ;
Es = u(b(b(t, t), t)) ;
Es = b(t, u(b(t, t))) ;
Es = b(t, b(t, u(t))) ;
Es = b(t, b(u(t), t)) ;
Es = b(u(t), b(t, t)) ;
Es = b(u(b(t, t)), t) ;
Es = b(b(t, t), u(t)) ;
Es = b(b(t, u(t)), t) ;
Es = b(b(u(t), t), t) ;
false.
Listing of answer
For those not familiar with DCG one import tool to have in your Prolog tool box is listing/1 which will convert the DCG to standard Prolog.
e.g.
?- listing(expression).
For the following listings I also changed the name of the variables by hand so that they are easier to follow and understand. When DCG is converted to standard Prolog two extra variables may appear as the last two arguments to a predicate. Here I have changed their names. They will start with S0
as the second to last argument and then progress as S1
, S2
, and so on until they are the last argument. Also if one of the input arguments is threaded through the code I have changed the name, e.g. U
to U0
and so on. I have also added as comments the clp(fd) constraints.
Using listing/1 on part of the answer:
% DCG
expression(U, B, E) -->
terminal(U, B, E)
| unary(U, B, E)
| binary(U, B, E).
% Standard Prolog
expression(U, B, E, S0, S1) :-
( terminal(U, B, E, S0, S1)
; unary(U, B, E, S0, S1)
; binary(U, B, E, S0, S1)
).
% DCG
terminal(0, 0, t) --> [t].
% Standard Prolog
terminal(0, 0, t, [t|S0], S0).
% DCG
unary(U, B, u(E)) -->
{
U1 #>= 0,
U #= U1 + 1
},
['u('],
expression_1(U1, B, E),
[')'].
% Standard Prolog
unary(U0, B, u(E), S0, S4) :-
true,
clpfd:clpfd_geq(U1, 0), % U1 #>= 0
( integer(U0)
-> ( integer(U1)
-> U0=:=U1+1 % U #= U1 + 1
; U2=U0,
clpfd:clpfd_equal(U2, U1+1) % U #= U1 + 1
)
; integer(U1)
-> ( var(U0)
-> U0 is U1+1 % U #= U1 + 1
; U2 is U1+1, % U #= U1 + 1
clpfd:clpfd_equal(U0, U2)
)
; clpfd:clpfd_equal(U0, U1+1) % U #= U1 + 1
),
S1=S0,
S1=['u('|S2],
expression_1(U1, B, E, S2, S3),
S3=[')'|S4].
% DCG
binary(U, B, b(E1, E2)) -->
{
U1 #>= 0,
U2 #>= 0,
U #= U1 + U2,
B1 #>= 0,
B2 #>= 0,
B #= B1 + B2 + 1
},
['b('],
expression_1(U1, B1, E1),
expression_1(U2, B2, E2),
[')'].
% Standard Prolog
binary(U0, B0, b(E1, E2), S0, S5) :-
true,
clpfd:clpfd_geq(U1, 0), % U1 #>= 0
true,
clpfd:clpfd_geq(U2, 0), % U2 #>= 0
( integer(U0)
-> ( integer(U1),
integer(U2)
-> U0=:=U1+U2 % U #= U1 + 1
; U3=U0,
clpfd:clpfd_equal(U3, U1+U2) % U #= U1 + 1
)
; integer(U1),
integer(U2)
-> ( var(U0)
-> U0 is U1+U2 % U #= U1 + 1
; U3 is U1+U2, % U #= U1 + 1
clpfd:clpfd_equal(U0, U3)
)
; clpfd:clpfd_equal(U0, U1+U2) % U #= U1 + 1
),
true,
clpfd:clpfd_geq(B1, 0), % B1 #>= 0
true,
clpfd:clpfd_geq(B2, 0), % B2 #>= 0
( integer(B0)
-> ( integer(B1),
integer(B2)
-> B0=:=B1+B2+1 % B #= B1 + B2 + 1
; B3=B0,
clpfd:clpfd_equal(B3, B1+B2+1) % B #= B1 + B2 + 1
)
; integer(B1),
integer(B2)
-> ( var(B0)
-> B0 is B1+B2+1 % B #= B1 + B2 + 1
; B3 is B1+B2+1, % B #= B1 + B2 + 1
clpfd:clpfd_equal(B0, B3)
)
; clpfd:clpfd_equal(B0, B1+B2+1) % B #= B1 + B2 + 1
),
S1=S0,
S1=['b('|S2],
expression_1(U1, B1, E1, S2, S3),
expression_1(U2, B2, E2, S3, S4),
S4=[')'|S5].
References to SWI-Prolog source code
If you wan to see the source that translates clp(fd) or DCG to standard prolog here are the links.
- clp(fd)
- dcg
Notes
Think of these as my personal notes in case I have to come back to this question in the future. No sense in keeping them to myself if they can help others.
With regards to
When is the use of length/2 required to constrain the size of DCG results and when can CLP(FD) be used?
After looking at the listing of the code that uses clp(fd) as a constraint I can start to understand why building parallel list and using length/2
is used. I did not expect the code to be that complex.
With regards to how clp(fd) avoids causing the error
Arguments are not sufficiently instantiated 1=:=_2692
it can be seen that it checks if the variable is bound or not
e.g.
integer(U1)
var(U0)
Evolution of code
Based on the answer by @lurker I was able evolve the code into this, which is to be able to generate all combinations of unique unary-binary trees given a list of unary ops, a list of binary ops and a list of terminals. While it can generate the combinations of the expressions, it still needs an intermediate step to rearrange the order of the items in the three lists before being used to generate the expressions I need.
% order of predicates matters
e( Uc , Uc , Bc , Bc , [Terminal|Terminal_s], Terminal_s , Unary_op_s , Unary_op_s , Binary_op_s , Binary_op_s , t , Terminal ).
e( [_|Uc0], Uc1, Bc0 , Bc1, Terminal_s_0 , Terminal_s_1, [Unary_op|Unary_op_s_0], Unary_op_s_1, Binary_op_s_0 , Binary_op_s_1, u(E0) , [op(Unary_op),[UE]] ) :-
e(Uc0 , Uc1, Bc0 , Bc1, Terminal_s_0 , Terminal_s_1, Unary_op_s_0 , Unary_op_s_1, Binary_op_s_0 , Binary_op_s_1, E0 , UE ).
e( Uc0 , Uc2, [_|Bc0], Bc2, Terminal_s_0 , Terminal_s_2, Unary_op_s_0 , Unary_op_s_2, [Binary_op|Binary_op_s_0], Binary_op_s_2, b(E0, E1), [op(Binary_op),[L,R]] ) :-
e(Uc0 , Uc1, Bc0 , Bc1, Terminal_s_0 , Terminal_s_1, Unary_op_s_0 , Unary_op_s_1, Binary_op_s_0 , Binary_op_s_1, E0 , L ),
e(Uc1 , Uc2, Bc1 , Bc2, Terminal_s_1 , Terminal_s_2, Unary_op_s_1 , Unary_op_s_2, Binary_op_s_1 , Binary_op_s_2, E1 , R ).
e(Uc, Bc, Terminal_s, Unary_op_s, Binary_op_s, Es, Ls) :-
length(Bs, Bc),
length(Us, Uc),
e(Us,[], Bs,[], Terminal_s, _, Unary_op_s, _, Binary_op_s, _, Es, Ls).
e(Unary_op_s, Binary_op_s, Terminal_s, Es, Ls) :-
length(Unary_op_s,Uc),
length(Binary_op_s,Bc),
length(Terminal_s,Ts),
Tc is Bc + 1,
Ts == Tc,
e(Uc, Bc, Terminal_s, Unary_op_s, Binary_op_s, Es, Ls).
This is the part I need
?- e([neg,ln],[add,sub],[[number(0)],[number(1)],[number(2)]],_,Ls);true.
Ls = [op(neg), [[op(ln), [[op(add), [[number(0)], [op(sub), [[number(1)], [number(2)]]]]]]]]] ;
Ls = [op(neg), [[op(ln), [[op(add), [[op(sub), [[number(0)], [number(1)]]], [number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(ln), [[op(sub), [[number(1)], [number(2)]]]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(sub), [[number(1)], [op(ln), [[number(2)]]]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(sub), [[op(ln), [[number(1)]]], [number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[op(ln), [[number(0)]]], [op(sub), [[number(1)], [number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[op(ln), [[op(sub), [[number(0)], [number(1)]]]]], [number(2)]]]]] ;
Ls = [op(neg), [[op(add), [[op(sub), [[number(0)], [number(1)]]], [op(ln), [[number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[op(sub), [[number(0)], [op(ln), [[number(1)]]]]], [number(2)]]]]] ;
Ls = [op(neg), [[op(add), [[op(sub), [[op(ln), [[number(0)]]], [number(1)]]], [number(2)]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(ln), [[op(sub), [[number(1)], [number(2)]]]]]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(sub), [[number(1)], [op(ln), [[number(2)]]]]]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(sub), [[op(ln), [[number(1)]]], [number(2)]]]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[number(1)], [op(neg), [[op(ln), [[number(2)]]]]]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[op(neg), [[number(1)]]], [op(ln), [[number(2)]]]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[op(neg), [[op(ln), [[number(1)]]]]], [number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(ln), [[op(sub), [[number(1)], [number(2)]]]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(sub), [[number(1)], [op(ln), [[number(2)]]]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(sub), [[op(ln), [[number(1)]]], [number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[op(ln), [[number(0)]]]]], [op(sub), [[number(1)], [number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[op(ln), [[op(sub), [[number(0)], [number(1)]]]]]]], [number(2)]]] ;
Ls = [op(add), [[op(neg), [[op(sub), [[number(0)], [number(1)]]]]], [op(ln), [[number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[op(sub), [[number(0)], [op(ln), [[number(1)]]]]]]], [number(2)]]] ;
Ls = [op(add), [[op(neg), [[op(sub), [[op(ln), [[number(0)]]], [number(1)]]]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [number(1)]]], [op(neg), [[op(ln), [[number(2)]]]]]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [op(neg), [[number(1)]]]]], [op(ln), [[number(2)]]]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [op(neg), [[op(ln), [[number(1)]]]]]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[op(neg), [[number(0)]]], [number(1)]]], [op(ln), [[number(2)]]]]] ;
Ls = [op(add), [[op(sub), [[op(neg), [[number(0)]]], [op(ln), [[number(1)]]]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[op(neg), [[op(ln), [[number(0)]]]]], [number(1)]]], [number(2)]]] ;
true.
And this is a nice quick way to see that they are unique.
?- e([neg,ln],[add,sub],[[number(0)],[number(1)],[number(2)]],Es,_);true.
Es = u(u(b(t, b(t, t)))) ;
Es = u(u(b(b(t, t), t))) ;
Es = u(b(t, u(b(t, t)))) ;
Es = u(b(t, b(t, u(t)))) ;
Es = u(b(t, b(u(t), t))) ;
Es = u(b(u(t), b(t, t))) ;
Es = u(b(u(b(t, t)), t)) ;
Es = u(b(b(t, t), u(t))) ;
Es = u(b(b(t, u(t)), t)) ;
Es = u(b(b(u(t), t), t)) ;
Es = b(t, u(u(b(t, t)))) ;
Es = b(t, u(b(t, u(t)))) ;
Es = b(t, u(b(u(t), t))) ;
Es = b(t, b(t, u(u(t)))) ;
Es = b(t, b(u(t), u(t))) ;
Es = b(t, b(u(u(t)), t)) ;
Es = b(u(t), u(b(t, t))) ;
Es = b(u(t), b(t, u(t))) ;
Es = b(u(t), b(u(t), t)) ;
Es = b(u(u(t)), b(t, t)) ;
Es = b(u(u(b(t, t))), t) ;
Es = b(u(b(t, t)), u(t)) ;
Es = b(u(b(t, u(t))), t) ;
Es = b(u(b(u(t), t)), t) ;
Es = b(b(t, t), u(u(t))) ;
Es = b(b(t, u(t)), u(t)) ;
Es = b(b(t, u(u(t))), t) ;
Es = b(b(u(t), t), u(t)) ;
Es = b(b(u(t), u(t)), t) ;
Es = b(b(u(u(t)), t), t) ;
true.
If you have been reading the comments then you know that one can use this with just one list as a constraint or no list as a constraint.
If you disable the list as constraints using
e(Uc, Bc, Terminal_s, Unary_op_s, Binary_op_s, Es, Ls) :-
e(_,[], _,[], Terminal_s, _, Unary_op_s, _, Binary_op_s, _, Es, Ls).
You get
?- e([neg,ln],[add,sub],[[number(0)],[number(1)],[number(2)]],_,Ls);true.
Ls = [number(0)] ;
Ls = [op(neg), [[number(0)]]] ;
Ls = [op(neg), [[op(ln), [[number(0)]]]]] ;
Ls = [op(neg), [[op(ln), [[op(add), [[number(0)], [number(1)]]]]]]] ;
Ls = [op(neg), [[op(ln), [[op(add), [[number(0)], [op(sub), [[number(1)], [number(2)]]]]]]]]] ;
Ls = [op(neg), [[op(ln), [[op(add), [[op(sub), [[number(0)], [number(1)]]], [number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [number(1)]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(ln), [[number(1)]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(ln), [[op(sub), [[number(1)], [number(2)]]]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(sub), [[number(1)], [number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(sub), [[number(1)], [op(ln), [[number(2)]]]]]]]]] ;
Ls = [op(neg), [[op(add), [[number(0)], [op(sub), [[op(ln), [[number(1)]]], [number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[op(ln), [[number(0)]]], [number(1)]]]]] ;
Ls = [op(neg), [[op(add), [[op(ln), [[number(0)]]], [op(sub), [[number(1)], [number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[op(ln), [[op(sub), [[number(0)], [number(1)]]]]], [number(2)]]]]] ;
Ls = [op(neg), [[op(add), [[op(sub), [[number(0)], [number(1)]]], [number(2)]]]]] ;
Ls = [op(neg), [[op(add), [[op(sub), [[number(0)], [number(1)]]], [op(ln), [[number(2)]]]]]]] ;
Ls = [op(neg), [[op(add), [[op(sub), [[number(0)], [op(ln), [[number(1)]]]]], [number(2)]]]]] ;
Ls = [op(neg), [[op(add), [[op(sub), [[op(ln), [[number(0)]]], [number(1)]]], [number(2)]]]]] ;
Ls = [op(add), [[number(0)], [number(1)]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[number(1)]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(ln), [[number(1)]]]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(ln), [[op(sub), [[number(1)], [number(2)]]]]]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(sub), [[number(1)], [number(2)]]]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(sub), [[number(1)], [op(ln), [[number(2)]]]]]]]]] ;
Ls = [op(add), [[number(0)], [op(neg), [[op(sub), [[op(ln), [[number(1)]]], [number(2)]]]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[number(1)], [number(2)]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[number(1)], [op(neg), [[number(2)]]]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[number(1)], [op(neg), [[op(ln), [[number(2)]]]]]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[op(neg), [[number(1)]]], [number(2)]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[op(neg), [[number(1)]]], [op(ln), [[number(2)]]]]]]] ;
Ls = [op(add), [[number(0)], [op(sub), [[op(neg), [[op(ln), [[number(1)]]]]], [number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [number(1)]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(ln), [[number(1)]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(ln), [[op(sub), [[number(1)], [number(2)]]]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(sub), [[number(1)], [number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(sub), [[number(1)], [op(ln), [[number(2)]]]]]]] ;
Ls = [op(add), [[op(neg), [[number(0)]]], [op(sub), [[op(ln), [[number(1)]]], [number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[op(ln), [[number(0)]]]]], [number(1)]]] ;
Ls = [op(add), [[op(neg), [[op(ln), [[number(0)]]]]], [op(sub), [[number(1)], [number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[op(ln), [[op(sub), [[number(0)], [number(1)]]]]]]], [number(2)]]] ;
Ls = [op(add), [[op(neg), [[op(sub), [[number(0)], [number(1)]]]]], [number(2)]]] ;
Ls = [op(add), [[op(neg), [[op(sub), [[number(0)], [number(1)]]]]], [op(ln), [[number(2)]]]]] ;
Ls = [op(add), [[op(neg), [[op(sub), [[number(0)], [op(ln), [[number(1)]]]]]]], [number(2)]]] ;
Ls = [op(add), [[op(neg), [[op(sub), [[op(ln), [[number(0)]]], [number(1)]]]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [number(1)]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [number(1)]]], [op(neg), [[number(2)]]]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [number(1)]]], [op(neg), [[op(ln), [[number(2)]]]]]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [op(neg), [[number(1)]]]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [op(neg), [[number(1)]]]]], [op(ln), [[number(2)]]]]] ;
Ls = [op(add), [[op(sub), [[number(0)], [op(neg), [[op(ln), [[number(1)]]]]]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[op(neg), [[number(0)]]], [number(1)]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[op(neg), [[number(0)]]], [number(1)]]], [op(ln), [[number(2)]]]]] ;
Ls = [op(add), [[op(sub), [[op(neg), [[number(0)]]], [op(ln), [[number(1)]]]]], [number(2)]]] ;
Ls = [op(add), [[op(sub), [[op(neg), [[op(ln), [[number(0)]]]]], [number(1)]]], [number(2)]]] ;
true.
and
?- e([neg,ln],[add,sub],[[number(0)],[number(1)],[number(2)]],Es,_);true.
Es = t ;
Es = u(t) ;
Es = u(u(t)) ;
Es = u(u(b(t, t))) ;
Es = u(u(b(t, b(t, t)))) ;
Es = u(u(b(b(t, t), t))) ;
Es = u(b(t, t)) ;
Es = u(b(t, u(t))) ;
Es = u(b(t, u(b(t, t)))) ;
Es = u(b(t, b(t, t))) ;
Es = u(b(t, b(t, u(t)))) ;
Es = u(b(t, b(u(t), t))) ;
Es = u(b(u(t), t)) ;
Es = u(b(u(t), b(t, t))) ;
Es = u(b(u(b(t, t)), t)) ;
Es = u(b(b(t, t), t)) ;
Es = u(b(b(t, t), u(t))) ;
Es = u(b(b(t, u(t)), t)) ;
Es = u(b(b(u(t), t), t)) ;
Es = b(t, t) ;
Es = b(t, u(t)) ;
Es = b(t, u(u(t))) ;
Es = b(t, u(u(b(t, t)))) ;
Es = b(t, u(b(t, t))) ;
Es = b(t, u(b(t, u(t)))) ;
Es = b(t, u(b(u(t), t))) ;
Es = b(t, b(t, t)) ;
Es = b(t, b(t, u(t))) ;
Es = b(t, b(t, u(u(t)))) ;
Es = b(t, b(u(t), t)) ;
Es = b(t, b(u(t), u(t))) ;
Es = b(t, b(u(u(t)), t)) ;
Es = b(u(t), t) ;
Es = b(u(t), u(t)) ;
Es = b(u(t), u(b(t, t))) ;
Es = b(u(t), b(t, t)) ;
Es = b(u(t), b(t, u(t))) ;
Es = b(u(t), b(u(t), t)) ;
Es = b(u(u(t)), t) ;
Es = b(u(u(t)), b(t, t)) ;
Es = b(u(u(b(t, t))), t) ;
Es = b(u(b(t, t)), t) ;
Es = b(u(b(t, t)), u(t)) ;
Es = b(u(b(t, u(t))), t) ;
Es = b(u(b(u(t), t)), t) ;
Es = b(b(t, t), t) ;
Es = b(b(t, t), u(t)) ;
Es = b(b(t, t), u(u(t))) ;
Es = b(b(t, u(t)), t) ;
Es = b(b(t, u(t)), u(t)) ;
Es = b(b(t, u(u(t))), t) ;
Es = b(b(u(t), t), t) ;
Es = b(b(u(t), t), u(t)) ;
Es = b(b(u(t), u(t)), t) ;
Es = b(b(u(u(t)), t), t) ;
true.
Either way is useful, I just have a personal preference for the ones generated from the constraints for reasons related to the project that uses them.
The next evolution came by referring back to Mat's answer.
e([number(0)] , t1 ) --> [].
e([number(1)] , t2 ) --> [].
e([number(2)] , t3 ) --> [].
e([op(neg),[Arg]] , u1(E) ) --> [_], e(Arg,E).
e([op(ln),[Arg]] , u2(E) ) --> [_], e(Arg,E).
e([op(add),[Left,Right]], b1(E0,E1) ) --> [_,_], e(Left,E0), e(Right,E1).
e([op(sub),[Left,Right]], b2(E0,E1) ) --> [_,_], e(Left,E0), e(Right,E1).
e(EL,Es) :-
length(Ls, _), phrase(e(EL,Es), Ls).
es_count(M, Count) :-
length([_|Ls], M),
findall(., phrase(e(_,_), Ls), Sols),
length(Sols, Count).
I won't show the results or explain this in detail as it should be trivial at this point. Of note is that it generates two different types of results, the first as a list and the second as compound terms.
Original 5 questions
The original question had 5 parts, but instead of creating a new question for that answer, parts of this question were removed so that the answer given by lurker could stay here.
- Can CLP(FD) be used with this solution and if so how?
- When is the use of length/2 required to constrain the size of DCG results and when can CLP(FD) be used?
- What other means are available to cause iterative deepening with DCG?
- How would I convert the non DCG solution back into a DCG version?
- As my DCG get more complex I will be needing more constraint variables. Is there a standard practice on how to handle this, or just follow the rinse and repeat methodology?