3

我正在尝试结合以前堆栈溢出问题中的一些纯谓词来制作我自己的谓词。

我想给出一个 c 列表(与它们相关联的事实 - 'ats')和一个 'feature' 术语,它有一个运算符和一个 'at' 的阈值。我想对 c 的列表进行分区,如果 c 没有来自“功能”的相应“at”,它将进入错误分区,否则操作员将测试该“c”的“at”并拆分c 合适。

例如:

?-cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).

应该导致:

Ts = [c3], %c3 has an at2 >= 10
Fs = [c1,c2]. %c1 has at2 <10 and c2 does not have an at2

这是我的代码:

:-use_module(library(clpfd)).

cpgpartition_ts_fs_feature([],[],[],_).
cpgpartition_ts_fs_feature([X|Xs0],Ts,Fs,Feature):-
    Feature = feature(At,_,Op,FValue),
    cpg_ats_i(X,AtList),
    atom_concat(#,Op,Op2), %make clpfd operator
    Test =..[Op2,AtValue3,FValue],
    if_(memberd_t(attribute(At,AtValue3),AtList),
       (
       if_(call(Test), (Ts=[X|Ts0],Fs=Fs0),
       (   Ts =Ts0,Fs=[X|Fs0]))
       )
       ,Fs=[X|Fs0]),
    cpgpartition_ts_fs_feature(Xs0,Ts0,Fs0,Feature).

if_(If_1, Then_0, Else_0) :-
   call(If_1, T),
   (  T == true -> call(Then_0)
   ;  T == false -> call(Else_0)
   ;  nonvar(T) -> throw(error(type_error(boolean,T),_))
   ;  /* var(T) */ throw(error(instantiation_error,_))
   ).

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

=(X, Y, T) :-
   (  X == Y -> T = true
   ;  X \= Y -> T = false
   ;  T = true, X = Y
   ;  T = false,
      dif(X, Y)                             % ISO extension
      % throw(error(instantiation_error,_)) % ISO strict
   ).

#=<(X,Y,Truth) :- X #=< Y #<==> B, bool01_t(B,Truth).

#<( X,Y,Truth) :- X #<  Y #<==> B, bool01_t(B,Truth).

#>( X,Y,Truth) :- X #>  Y #<==> B, bool01_t(B,Truth).

#>=(X,Y,Truth) :- X #>= Y #<==> B, bool01_t(B,Truth).

list_memberd_t([]    ,_,false).
list_memberd_t([Y|Ys],X,Truth) :-
   if_(X=Y, Truth=true, list_memberd_t(Ys,X,Truth)).

list_memberd_truth(Xs,X,Truth) :- list_memberd_t(Xs,X,Truth).

memberd_t(X,Xs,Truth) :- list_memberd_t(Xs,X,Truth).

value_intvalue(attribute(_A,X),attribute(_A,Y)):-
        AtValue2 is X *100, %Convert decimal number to integer.
        Y is integer(AtValue2).

cpg_ats_i(C,AtList):-
        cpg_ats(C,Ats),
        maplist(value_intvalue,Ats,AtList).

cpg_ats(c1,[attribute(at1,0.5),attribute(at2,0.03)]).
cpg_ats(c2,[attribute(at1,0.02)]).
cpg_ats(c3,[attribute(at2,0.1),attribute(at3,0.04),attribute(at4,0.08)]).

尝试测试查询时,我得到:

cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).
Fs = [c1, c2] ;
Fs = [c1, c2, c3] ;
Fs = [c1, c2] ;
Fs = [c1, c2, c3].

有趣的是,如果 clist 的顺序不同,结果会发生变化。

?- cpgpartition_ts_fs_feature([c3,c1,c2],Ts,Fs,feature(at2,_,>=,10)).
Ts = [c3|_12950],
Fs = [c1, c2] ;
Ts = [c3|_12950],
Fs = [c1, c2] ;
Fs = [c3, c1, c2] ;
Fs = [c3, c1, c2].

我认为这是因为以下查询返回带有dif/2约束的结果,这些约束似乎不适合我正在尝试做的事情,我只想要具体的解决方案。

    ?- cpg_ats_i(C,Ats),   if_(memberd_t(attribute(at2,AtValue),Ats),Q=true,Q=false).
C = c1,
Ats = [attribute(at1, 50), attribute(at2, 3)],
AtValue = 3,
Q = true ;
C = c1,
Ats = [attribute(at1, 50), attribute(at2, 3)],
Q = false,
dif(AtValue, 3) ;
C = c2,
Ats = [attribute(at1, 2)],
Q = false ;
C = c3,
Ats = [attribute(at2, 10), attribute(at3, 4), attribute(at4, 8)],
AtValue = 10,
Q = true ;
C = c3,
Ats = [attribute(at2, 10), attribute(at3, 4), attribute(at4, 8)],
Q = false,
dif(AtValue, 10).

此外,目标是让这段代码在大量数据上运行,c 的列表将有数十万的长度,每个 c 可能有 50k 的 ats,我该如何计算内存需求?使用不纯谓词的不同方法是否可能占用更少的内存?

4

3 回答 3

4

正如您所提到的,问题出在定义中的 dif(X,Y) 行中:

=(X, Y, T) :-
   (  X == Y -> T = true
   ;  X \= Y -> T = false
   ;  T = true, X = Y
   ;  T = false,
      dif(X, Y)                             % ISO extension
      % throw(error(instantiation_error,_)) % ISO strict
   ).

那是因为如果你尝试:

memberd_t(attribute(at2,X),[attribute(at1,0.5),attribute(at2,0.03)],T).
X = 0.03,
T = true ;
T = false,
dif(X, 0.03).

这里给出解决方案的选择点:T = false,dif(X, 0.03).将导致执行的部分Fs=[X|Fs0]

if_(memberd_t(attribute(At,AtValue3),AtList),
       (
       if_(call(Test), (Ts=[X|Ts0],Fs=Fs0),
       (   Ts =Ts0,Fs=[X|Fs0]))
       )
       ,Fs=[X|Fs0]),

这也不是正确的响应,因为如果您Atlist希望memberd_t返回的属性(at2,0.03)X = 0.03, T = true将触发Then_0部分if_/3(并且没有其他解决方案 T = false 将导致其他选择点执行 Else_0 部分)。

所以你可以删除 T = false,dif(X, Y) of =/3,现在让我们试试:

?- cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).
Fs = [c1, c2].

很好,但是Ts在哪里??

所以还有一个bug:

上面说它Fs = [c1,c2]每个 Ts 都成功。那是因为执行其中Else_0的一部分if_/3会满足Fs您不限制Ts列表的列表,只需保留 asTs并稍后调用cpgpartition_ts_fs_feature(Xs0,Ts0,Fs0,Feature)另一个Ts0独立于 Ts 的列表。所以添加:

if_(memberd_t(attribute(At,AtValue3),AtList),
       (
        if_(call(Test), (Ts=[X|Ts0],Fs=Fs0), (Ts =Ts0,Fs=[X|Fs0]))
       )
       ,(Fs=[X|Fs0], Ts = Ts0 )),
                     ^^^^^^^^
                     here added 

最后,我按照@false 的建议,最好用它替换Test =..[Op2,AtValue3,FValue], ..., call(Test)call(Op2,AtValue3,FValue)因为它call/N是 ISO 的一部分,它适合原始的 Mycroft O'Keefe 类型系统。

现在让我们再试一次:

?- cpgpartition_ts_fs_feature([c1,c2,c3],Ts,Fs,feature(at2,_,>=,10)).
Ts = [c3],
Fs = [c1, c2].

似乎正确和确定性:) !!。

至于您问题的内存部分,我不太确定,但更喜欢不会为内存效率留下选择点的确定性谓词。使用纯谓词将使您的编程更具关系性并具有更好的行为,但我不确定是否if_/3如此高效,因为它包含许多调用,但我不确定其他人是否可以更清楚地回答这部分。

于 2017-09-27T20:53:39.093 回答
1

感谢 Coder 的回答,我想出了:

cpgpartition_ts_fs_feature([],[],[],_).
cpgpartition_ts_fs_feature([X|Xs0],Ts,Fs,feature(At,_,Op,FValue)):-
    cpg_ats_i(X,AtList),
    atom_concat(#,Op,Op2), %make clpfd operator
    maplist(atterm_atname,AtList,Ats),
    if_(memberd_t(At,Ats),
      (
      memberchk(attribute(At,AtValue3),AtList),
      if_(call(Op2,AtValue3,FValue), (Ts=[X|Ts0],Fs=Fs0),
        (   Ts =Ts0,Fs=[X|Fs0]))
      ),
      (Fs=[X|Fs0],Ts=Ts0)
    ),
    cpgpartition_ts_fs_feature(Xs0,Ts0,Fs0,feature(At,_,Op,FValue)).


atterm_atname(attribute(At,_),At).

这使我能够在不更改=/3.

于 2017-09-28T07:09:18.943 回答
0

当前建议的 if_/3 实现是拙劣的,因为它将选择点放在具体化上,而不是放在 if-then-else itsef 上。这是一个示例缺陷:

Welcome to SWI-Prolog (threaded, 64 bits, version 8.1.4)

?- call(','(X=Y,2=3),B).
X = Y,
B = false ;  %%% a bloody choice point %%%
B = false,
dif(X, Y). 

在这里,我们看到 SWI-Prolog 中来自 CLP(FD) 的例如 #/\ 的结合更好的智能。不创建选择点:

Welcome to SWI-Prolog (threaded, 64 bits, version 8.1.4)

?- X #= Y #/\ 2 #= 3 #<==> B.
B = 0,
X in inf..sup,
Y in inf..sup. 

我目前正在研究一个更好的 if_/3,它将这种智能融入到它的工作中。更好的 if_/3 的基本模式将是:

if(Cond, Then, Else) :-
   reify(Cond, Bool),
   thenelse(Bool, Then, Else)

thenelse(1, Then, _) :- Then.
thenelse(0, _, Else) :- Else. 

我们的想法是不要将任何选择点放入 reify/2 中,尽可能避免使用它们。目前 (=)/3 创建一个选择点,组合时不好

条件。或许我们也可以在代码的不同地方安排相同的条件,共享相同的布尔指示变量。正在努力...

于 2019-04-06T16:57:51.740 回答