如何使用具有 CLP(FD) 和多个约束的 DCG 枚举组合 [英] How to enumerate combinations using DCGs with CLP(FD) and multiple constraints

查看:13
本文介绍了如何使用具有 CLP(FD) 和多个约束的 DCG 枚举组合的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

这个问题从 Mat 的 answer枚举二叉树的算法改进只有一个输入值决定二叉树的所有节点的数量,并且需要能够有两个输入值,其中一个是一元的数量节点,另一个是二进制节点的数量.

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.

虽然我能够通过使用 listing/1 得出解决方案 和线程额外的状态变量:

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,[]).

注意:请参阅下面的 Prolog 输出.

Note: See Prolog output below.

我对 length/2 作为一个约束,它的使用并不明显,而且它没有使用 DCG.从之前对其他问题的其他尝试中,我知道使用数字作为约束会失败,例如

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).

但是在搜索时我发现了使用 CLP(FD) 与 DCG,并决定尝试一下.

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).

但是,这会导致无限循环不返回任何结果.
注意:我了解 CLP(FD) 的概念,但我对它的实际使用几乎没有.

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.

所以问题是:

  1. CLP(FD) 能否与此解决方案一起使用?如果可以,如何使用?
  2. 如何将非 DCG 解决方案转换回 DCG 版本?

补充

起始代码和清单

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 输出

?- 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.

答案列表

对于那些不熟悉 DCG 的人来说,Prolog 工具箱中的一个导入工具是 listing/1 将 DCG 转换为标准 Prolog.

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.

例如

?- listing(expression).  

对于以下列表,我还手动更改了变量的名称,以便更容易理解和理解.当 DCG 转换为标准 Prolog 时,两个额外的变量可能会作为谓词的最后两个参数出现.在这里,我改变了他们的名字.它们将从 S0 作为倒数第二个参数开始,然后按 S1S2 等顺序进行,直到它们成为最后一个参数.此外,如果输入参数之一通过代码进行线程化,我已更改名称,例如UU0 等等.我还添加了 clp(fd) 约束作为注释.

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.

在部分答案中使用 listing/1:

% 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].

对 SWI-Prolog 源代码的引用

如果您想查看将 clp(fd) 或 DCG 转换为标准 prolog 的源代码,请点击此处的链接.

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.

将这些视为我的个人笔记,以防我将来必须回到这个问题.如果他们能帮助别人,把他们留给我自己是没有意义的.

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.

关于

什么时候需要使用 length/2 来约束 DCG 结果的大小,什么时候可以使用 CLP(FD)?

When is the use of length/2 required to constrain the size of DCG results and when can CLP(FD) be used?

查看使用 clp(fd) 作为约束的代码列表后,我可以开始理解为什么要使用构建并行列表和使用 length/2.我没想到代码会那么复杂.

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.

关于 clp(fd) 如何避免导致错误

With regards to how clp(fd) avoids causing the error

参数没有充分实例化 1=:=_2692

Arguments are not sufficiently instantiated 1=:=_2692

可以看出它检查了变量是否被绑定

it can be seen that it checks if the variable is bound or not

例如

integer(U1)
var(U0)

代码的演变

根据@lurker 的回答,我能够将代码演变成这样,即能够在给定一元操作列表、二元操作列表和终端.虽然它可以生成表达式的组合,但它仍然需要一个中间步骤来重新排列三个列表中的项目的顺序,然后才能用于生成我需要的表达式.

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).

这是我需要的部分

?- 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).

你得到

?- 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.

?- 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.

下一个演变来自于参考 Mat 的答案.

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.

原始问题有 5 个部分,但不是为该答案创建新问题,而是删除了此问题的部分内容,以便 lurker给出的答案可以留在这里.

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.

  1. CLP(FD) 能否与此解决方案一起使用?如果可以,如何使用?
  2. 什么时候需要使用 length/2 来限制 DCG 结果的大小?什么时候可以使用 CLP(FD)?
  3. 还有哪些其他方法可以通过 DCG 实现迭代深化?
  4. 如何将非 DCG 解决方案转换回 DCG 版本?
  5. 随着我的 DCG 变得越来越复杂,我将需要更多的约束变量.有没有关于如何处理这个问题的标准做法,或者只是按照 冲洗并重复方法?

推荐答案

带计数器的基本树表达式解析器

假设二元一元树的复合项表示(eg, b(t,u(b(t,t,)))),这里是基本解析器.CLP(FD) 通常推荐用于对整数进行推理.

Assuming a compound term representation for binary-unary trees (e.g., b(t,u(b(t,t,)))), here is a basic parser. CLP(FD) is generally recommended for reasoning over integers.

expression(U, B, E) :-
    terminal(U, B, E).
expression(U, B, E) :-
    unary(U, B, E).
expression(U, B, E) :-
    binary(U, B, E).

terminal(0, 0, t).

unary(U, B, u(E)) :-
    U1 #>= 0,
    U #= U1 + 1,
    expression(U1, B, E).

binary(U, B, b(E1,E2)) :-
    U1 #>= 0, U2 #>= 0,
    U #= U1 + U2,
    B1 #>= 0, B2 #>= 0,
    B #= B1 + B2 + 1,
    expression(U1, B1, E1),
    expression(U2, B2, E2).

我在这里特意做了几件事.一种是使用 CLP(FD) 对一元和二元项的计数进行更多的关系推理.我所做的另一件事是将更简单的 expression/3 子句放在首位,它不进行递归.这样,Prolog 将在探索可能的解决方案的过程中首先到达终端.

There are a couple of things I've done intentionally here. One is to use CLP(FD) to give me more relational reasoning over the counts for unary and binary terms. The other thing I've done is put the simpler expression/3 clause first which doesn't do recursion. That way, Prolog will hit terminals first in the process of exploring possible solutions.

执行示例:

| ?- expression(1,2,E).

E = u(b(t,b(t,t))) ? a

E = u(b(b(t,t),t))

E = b(t,u(b(t,t)))

E = b(t,b(t,u(t)))

E = b(t,b(u(t),t))

E = b(u(t),b(t,t))

E = b(u(b(t,t)),t)

E = b(b(t,t),u(t))

E = b(b(t,u(t)),t)

E = b(b(u(t),t),t)

(1 ms) no


| ?- expression(U, B, E).

B = 0
E = t
U = 0 ? ;

B = 0
E = u(t)
U = 1 ? ;

B = 0
E = u(u(t))
U = 2 ? ;
...

使用 DCG 进行顺序表示

DCG 用于解析序列.复合词可以被解析为标记或字符的序列,通过使用 DCG,可以将其映射到复合词本身.例如,我们可以将复合树项 b(t,u(b(t,t))) 表示为 [b, '(', t, u, '(', b, '(', t, t, ')', ')', ')'].然后我们可以使用 DCG 并包含该表示.这是一个用这种序列格式反映上述实现的 DCG:

A DCG is used for parsing sequences. The compound term can be parsed as a sequence of tokens or characters, which can, through the use of a DCG, be mapped to the compound term itself. We might, for example, represent the compound tree term b(t,u(b(t,t))) as [b, '(', t, u, '(', b, '(', t, t, ')', ')', ')']. Then we can use a DCG and include that representation. Here's a DCG that reflects the above implementation with this sequence format:

expression(U, B, E) -->
    terminal(U, B, E) |
    unary(U, B, E) |
    binary(U, B, E).

terminal(0, 0, t) --> [t].

unary(U, B, u(E)) -->
    [u, '('],
    { U1 #>= 0, U #= U1 + 1 },
    expression(U1, B, E),
    [')'].

binary(U, B, b(E1, E2)) -->
    [b, '('],
    { U1 #>= 0, U2 #>= 0, U #= U1 + U2, B1 #>= 0, B2 #>= 0, B #= B1 + B2 + 1 },
    expression(U1, B1, E1),
    expression(U2, B2, E2),
    [')'].

再次,我把 terminal//3 作为 expression//3 的第一道查询.您可以看到此版本与非 DCG 版本之间的并行性.以下是执行示例.

Again, I put the terminal//3 as the first course of query for expression//3. You can see the parallelism between this and the non-DCG version. Here are example executions.

| ?-  phrase(expression(1,2,E), S).

E = u(b(t,b(t,t)))
S = [u,'(',b,'(',t,b,'(',t,t,')',')',')'] ? a

E = u(b(b(t,t),t))
S = [u,'(',b,'(',b,'(',t,t,')',t,')',')']

E = b(t,u(b(t,t)))
S = [b,'(',t,u,'(',b,'(',t,t,')',')',')']

E = b(t,b(t,u(t)))
S = [b,'(',t,b,'(',t,u,'(',t,')',')',')']

E = b(t,b(u(t),t))
S = [b,'(',t,b,'(',u,'(',t,')',t,')',')']

E = b(u(t),b(t,t))
S = [b,'(',u,'(',t,')',b,'(',t,t,')',')']

E = b(u(b(t,t)),t)
S = [b,'(',u,'(',b,'(',t,t,')',')',t,')']

E = b(b(t,t),u(t))
S = [b,'(',b,'(',t,t,')',u,'(',t,')',')']

E = b(b(t,u(t)),t)
S = [b,'(',b,'(',t,u,'(',t,')',')',t,')']

E = b(b(u(t),t),t)
S = [b,'(',b,'(',u,'(',t,')',t,')',t,')']

no

| ?-  phrase(expression(U,B,E), S).

B = 0
E = t
S = [t]
U = 0 ? ;

B = 0
E = u(t)
S = [u,'(',t,')']
U = 1 ? ;

B = 0
E = u(u(t))
S = [u,'(',u,'(',t,')',')']
U = 2 ?
...

希望这可以回答问题#1,也许是#4.但是,将任何谓词集转换为 DCG 的一般问题更加困难.正如我上面提到的,DCG 真的是用来处理序列的.

Hopefully this answers question #1, and perhaps #4 by example. The general problem of converting any set of predicates to a DCG, though, is more difficult. As I mentioned above, DCG is really for handling sequences.

使用length/2控制解序

回答#2,既然我们有一个可以正确生成解决方案的 DCG 解决方案,我们可以通过使用 length/2 来控制给出的解决方案的顺序,它将按照以下顺序提供解决方案长度优先而不是深度优先.你可以从头开始约束长度,这比在递归的每一步都约束长度更有效和高效,这是多余的:

In answer to #2, now that we have a DCG solution that will generate solutions properly, we can control the order of solutions given by using length/2, which will provide solutions in order of length rather than depth-first. You can constrain the length right from the beginning, which is more effective and efficient than constraining the length at each step in the recursion, which is redundant:

?- length(S, _), phrase(expression(U,B,E), S).

B = 0
E = t
S = [t]
U = 0 ? ;

B = 0
E = u(t)
S = [u,'(',t,')']
U = 1 ? ;

B = 1
E = b(t,t)
S = [b,'(',t,t,')']
U = 0 ? ;

B = 0
E = u(u(t))
S = [u,'(',u,'(',t,')',')']
U = 2 ? ;

B = 1
E = u(b(t,t))
S = [u,'(',b,'(',t,t,')',')']
U = 1 ? ;

B = 1
E = b(t,u(t))
S = [b,'(',t,u,'(',t,')',')']
U = 1 ? ;

B = 1
E = b(u(t),t)
S = [b,'(',u,'(',t,')',t,')']
U = 1 ? 
...

如果我使用一元二叉树的顺序表示来约束解决方案,而不是用于解析,我会去掉括号,因为它们在表示中不是必需的:

If I were using the sequential representation of the unary-binary tree for constraining solutions, not for parsing, I would get rid of the parentheses since they aren't necessary in the representation:

unary(U, B, u(E)) -->
    [u],
    { U1 #>= 0, U #= U1 + 1 },
    expression(U1, B, E).

binary(U, B, b(E1, E2)) -->
    [b],
    { U1 #>= 0, U2 #>= 0, U #= U1 + U2, B1 #>= 0, B2 #>= 0, B #= B1 + B2 + 1 },
    expression(U1, B1, E1),
    expression(U2, B2, E2).

这可能更有效一些,因为对应于无效序列的列表长度数量较少.这导致:

It's probably a little more efficient since there are a fewer number of list lengths that correspond to invalid sequences. This results in:

| ?- length(S, _), phrase(expression(U, B, E), S).

B = 0
E = t
S = [t]
U = 0 ? ;

B = 0
E = u(t)
S = [u,t]
U = 1 ? ;

B = 0
E = u(u(t))
S = [u,u,t]
U = 2 ? ;

B = 1
E = b(t,t)
S = [b,t,t]
U = 0 ? ;

B = 0
E = u(u(u(t)))
S = [u,u,u,t]
U = 3 ? ;

B = 1
E = u(b(t,t))
S = [u,b,t,t]
U = 1 ? ;

B = 1
E = b(t,u(t))
S = [b,t,u,t]
U = 1 ? ;

B = 1
E = b(u(t),t)
S = [b,u,t,t]
U = 1 ? ;

B = 0
E = u(u(u(u(t))))
S = [u,u,u,u,t]
U = 4 ? ;

B = 1
E = u(u(b(t,t)))
S = [u,u,b,t,t]
U = 2 ? ;
...

所以,如果你有一个通用术语的递归定义,Term,它可以表示为一个序列(因此,使用 DCG),那么 length/2 可以通过这种方式来约束解并按序列长度对它们进行排序,这对应于原始项的某些排序.实际上,length/2 的引入可能会阻止您的 DCG 在不提供任何解决方案的情况下无限递归,但我仍然希望通过尝试组织逻辑来让 DCG 表现得更好先走航站楼.

So, if you have a recursive definition of a general term, Term, which can be expressed as a sequence (thus, using a DCG), then length/2 can be used in this way to constrain the solutions and order them by length of sequence, which corresponds to some ordering of the original terms. Indeed, the introduction of the length/2 may prevent your DCG from infinitely recursing without presenting any solutions, but I would still prefer to have the DCG be better behaved to start with by attempting to organize the logic to walk the terminals first.

这篇关于如何使用具有 CLP(FD) 和多个约束的 DCG 枚举组合的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆