问题 不经过一次删除不正确的后续解


我有一个谓词,找到正确的解决方案,但接着找到不正确的解决方案。

?- data(D),data_threshold_nonredundantbumps(D,5,Bs),write(D).
[3,6,7,8,2,4,5,6,9,4,7,3]
D = [3, 6, 7, 8, 2, 4, 5, 6, 9|...],
Bs = [bump([11], [7]), bump([8, 9], [6, 9]), bump([2, 3, 4], [6, 7, 8])] ;
[3,6,7,8,2,4,5,6,9,4,7,3]
D = [3, 6, 7, 8, 2, 4, 5, 6, 9|...],
Bs = [bump([8, 9], [6, 9]), bump([2, 3, 4], [6, 7, 8])] ;
[3,6,7,8,2,4,5,6,9,4,7,3]
D = [3, 6, 7, 8, 2, 4, 5, 6, 9|...],
Bs = [bump([8], [6]), bump([2, 3, 4], [6, 7, 8])] ;
[3,6,7,8,2,4,5,6,9,4,7,3]
D = [3, 6, 7, 8, 2, 4, 5, 6, 9|...],
Bs = [bump([9], [9]), bump([2, 3, 4], [6, 7, 8])] ;
[3,6,7,8,2,4,5,6,9,4,7,3]
D = [3, 6, 7, 8, 2, 4, 5, 6, 9|...],
Bs = [bump([11], [7]), bump([2, 3, 4], [6, 7, 8])] ;
[3,6,7,8,2,4,5,6,9,4,7,3]
D = [3, 6, 7, 8, 2, 4, 5, 6, 9|...],
Bs = [bump([2, 3, 4], [6, 7, 8])] ;

等等

我们的想法是,它将在数据中找到所有非冗余的凸起,其中凸起是连续的子列表 data 就在上面 threshold,返回有序(按大小)列表 bump/2s 其中第一个arg of bump / 2是一个来自数据的指标列表,第二个arg是值列表。所以 bump([2, 3, 4], [6, 7, 8]) 意味着在数据指数2,3和4高于5时,它们是6,7,8。

如何添加条件以便找不到这些额外的解决方案? - 没有使用 once/1

如果我的代码可以通过其他方式简化,请告诉我。这似乎有点复杂,它正在尝试做什么。

所以:

这是我的代码:

:-use_module(library(clpfd)).

fd_length(L, N) :-
 N #>= 0,
 fd_length(L, N, 0).

fd_length([], N, N0) :-
 N #= N0.
fd_length([_|L], N, N0) :-
 N1 is N0+1,
 N #>= N1,
 fd_length(L, N, N1).

equidistant_stride([],_).
equidistant_stride([Z|Zs],D) :-
 foldl(equidistant_stride_(D),Zs,Z,_).

equidistant_stride_(D,Z1,Z0,Z1) :-
 Z1 #= Z0+D.

consecutive_ascending_integers(Zs) :-
 equidistant_stride(Zs,1).

consecutive_ascending_integers_from(Zs,Z0) :-
 Zs = [Z0|_],
 consecutive_ascending_integers(Zs).

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

if_(C_1,Then_0,Else_0) -->
 { call(C_1,Truth) },
 { functor(Truth,_,0) },  % safety check
 (  { Truth == true }  -> phrase(Then_0)
 ;  { Truth == false },   phrase(Else_0)
 ).

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


 #=<(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).

tinclude(P_2,Xs,Zs) :-
 list_tinclude_list(Xs,P_2,Zs).

list_tinclude_list([],   _P_2,[]).
list_tinclude_list([i_v(E0,E1)|Es],P_2,Fs0) :-
 if_(call(P_2,E1), Fs0 = [i_v(E0,E1)|Fs], Fs0 = Fs),
 list_tinclude_list(Es,P_2,Fs).


tfilter(P_2,As,Bs) :-
 tinclude(P_2,As,Bs).

%% =====================================================================
%% =====================================================================

data([5,6,7,8,3,2,6,7]).

list_index_element(L,I,E):-
 nth1(I,L,E).  

filter(Threshold,DataPairs,FilterdPairs):-
 tfilter(#<(Threshold),DataPairs,FilterdPairs).

i_v_pair(I,V,i_v(I,V)).

data_indices_indicespairs(D,Is,Pairs):-
 same_length(D,Is),
 consecutive_ascending_integers_from(Is,1),
 maplist(i_v_pair,Is,D,Pairs).

list_ascending(List,MinLength,MaxLength):-
 Max in MinLength..MaxLength,
 labeling([max(Max)],[Max]),
 fd_length(List,Max),
 consecutive_ascending_integers(List).

region_minlength_maxlength(Region,MinLength,MaxLength,All):-
 list_ascending(Region,MinLength,MaxLength),
 append(_Before,End,All),
 append(Region,_End2,End).

data_threshold_bumpvalues_bumplocation(Data,Threshold,Bumpvalues,Bumplocation):-
 length(Data,MaxBump),
 data_indices_indicespairs(Data,_Is,Pairs),
 filter(Threshold,Pairs,FilteredPairs),
 maplist(i_v_pair,FilteredIndices,_FilteredValues,FilteredPairs),
 %Test =test(FilteredIndexes,FilteredValues),
 dif(Bumplocation,[]),
 region_minlength_maxlength(Bumplocation,0,MaxBump,FilteredIndices),
 maplist(list_index_element(Data), Bumplocation,Bumpvalues).


list_first_last([H|T],H,L):-
 last(T,L).

listoflists_firsts_lasts(Listoflists,Firsts,Lasts):-
 maplist(list_first_last,Listoflists,Firsts,Lasts).

%start is not between location1 and location2
start_location1_location2(Start,Location1,Location2) :-
 #\(   Location1 #=< Start,
 Start #=< Location2).

bumplocation_notsublist_of_any_acs(Bumplocation,Acs):-
 listoflists_firsts_lasts(Acs,Firsts,Lasts),
 %the start of bumplocation can not be between the start of any Acs
 Bumplocation =[Bumpstart|_],
 maplist(start_location1_location2(Bumpstart),Firsts,Lasts).


loc_val_bump(Location,Value,bump(Location,Value)).

data_bumplocations_bumpvalues(Data,Bumplocations,Bumpvalues):-
 maplist(list_index_element(Data),Bumplocations,Bumpvalues).

%this works but finds extra solutins so needs to be refined.
data_threshold_nonredundantbumps(Data,Threshold,Bumps):-
 data_threshold_nonredundantbumps_ac(Data,Threshold,Nonredundantbumpslocations,[]),
 maplist(data_bumplocations_bumpvalues(Data),Nonredundantbumpslocations,Nonredundantbumps),
 maplist(loc_val_bump,Nonredundantbumpslocations,Nonredundantbumps,Bumps).

data_threshold_nonredundantbumps_ac(Data,Threshold,Nonredundantbumps,Ac0):-
 bumplocation_notsublist_of_any_acs(Bumplocation,Ac0),
 data_threshold_bumpvalues_bumplocation(Data,Threshold,_Bumpvalues,Bumplocation),
 append([Bumplocation],Ac0,Ac1),
 data_threshold_nonredundantbumps_ac(Data,Threshold,Nonredundantbumps,Ac1).

data_threshold_nonredundantbumps_ac(_Data,_Threshold,Ac0,Ac0).

8742
2017-07-23 15:50


起源



答案:


我的印象是你稍微过度思考。有一个直截了当的表述 运行 超过阈值的数字,可以通过在列表的单个遍历中从头到尾考虑元素来定义。特别是,我们这样做  需要 append/3 去做这个。

一定要考虑使用 DCG表示法 ()在描述时 名单 在Prolog。在这种情况下,需要花一点时间来决定如何最好地应用DCG,因为我们正在描述  列表:

  • 的清单 运行 (连续元素超过阈值)
  • 在运行中,列表 指数 和

然而,除了一些技巧和扩展,DCG基本上只允许我们描述一个  列表,而不是同时单独的列表。因此,我们可以使用这种功能强大且可能非常合适的机制,并且必须选择我们要应用的列表 主要

在下文中,我展示了一个使用DCG来描述列表的解决方案 凸块/ 1 术语,也就是说,我“专用”机制来描述上面提到的第一种列表,并使用另一个DCG来描述 第二 一种列表,我通过它调用 phrase/2 来自第一个DCG。

data_threshold_bumps(Ds, T, Bs) :-
        phrase(bumps(Ds, 1, T), Bs).

bumps([], _, _) --> [].
bumps([D|Ds0], I0, T) -->
        { D #> T,
          phrase(bump(D, T, Ds0, Ds, I0, I), Bs) },
        [bump(Bs)],
        bumps(Ds, I, T).
bumps([D|Ds0], I0, T) -->
        { D #=< T,
          I #= I0 + 1 },
        bumps(Ds0, I, T).


bump(D, T, Ds0, Ds, I0, I) --> [I0-D],
        { I1 #= I0 + 1 },
        run(Ds0, Ds, T, I1, I).

run([], [], _, I, I) --> [].
run([D|Ds0], Ds, T, I0, I) --> [I0-D],
        { D #> T,
          I1 #= I0 + 1 },
        run(Ds0, Ds, T, I1, I).
run([D|Ds0], [D|Ds0], T, I, I) -->
        { D #=< T }.

示例查询和答案:

? -  data_threshold_bumps([3,6,7,8,2,4,5,6,9,4,7,3],5,Bs)。
Bs = [bump([2-6,3-7,4-8]),bump([8-6,9-9]),bump([11-7])] ;
假。

请注意,事实并非如此 相当 您需要的完全相同的数据表示,但将它转换为那个是微不足道的。

以下是一些改进此解决方案的想法,从更容易到更难:

  • 使用,摆脱不必要的选择点 if_/3
  • 使用DCG表示法真的有意义吗? bumps//3 和 run//5 在上面的代码?在这里使用DCG比常规谓词有什么好处和缺点?
  • 玩不同的问题视图:你能转​​动DCG视图吗?例如,如何描述实际情况 数据 使用DCG,而不是颠簸?
  • 在您发布的代码中追踪不需要的解决方案的来源。

顺便说一句,到 否定 一个(可再生的)CLP(FD)约束,你需要使用 (#/\)/2 表示连词。确实如此  与...合作 (,)/2


7
2017-07-23 18:05



你可能意味着 (',')/2 - false
谢谢你的解决方案。我的不需要的解决方案是否与我使用append有关?试着想一想你的想法:) - user27815
即使没有查看代码的细节,我也会这样说 append/3 绝对是其中之一 主要嫌疑人 在这种情况下产生的答案比我们想要的多。注意经常使用 append/3 几乎总是表明您的数据结构存在问题:您应该重写算法,以便始终可以推断列表的头部(例如: Ls = [First,Second|Rest]),或使用DCG更有效地描述列表。 - mat
就个人而言,当列表以某种方式涉及时,我几乎总是使用DCG表示法来描述它们,所以,可能是的。 - mat
再次感谢您的建议和专业知识。 - user27815


答案:


我的印象是你稍微过度思考。有一个直截了当的表述 运行 超过阈值的数字,可以通过在列表的单个遍历中从头到尾考虑元素来定义。特别是,我们这样做  需要 append/3 去做这个。

一定要考虑使用 DCG表示法 ()在描述时 名单 在Prolog。在这种情况下,需要花一点时间来决定如何最好地应用DCG,因为我们正在描述  列表:

  • 的清单 运行 (连续元素超过阈值)
  • 在运行中,列表 指数 和

然而,除了一些技巧和扩展,DCG基本上只允许我们描述一个  列表,而不是同时单独的列表。因此,我们可以使用这种功能强大且可能非常合适的机制,并且必须选择我们要应用的列表 主要

在下文中,我展示了一个使用DCG来描述列表的解决方案 凸块/ 1 术语,也就是说,我“专用”机制来描述上面提到的第一种列表,并使用另一个DCG来描述 第二 一种列表,我通过它调用 phrase/2 来自第一个DCG。

data_threshold_bumps(Ds, T, Bs) :-
        phrase(bumps(Ds, 1, T), Bs).

bumps([], _, _) --> [].
bumps([D|Ds0], I0, T) -->
        { D #> T,
          phrase(bump(D, T, Ds0, Ds, I0, I), Bs) },
        [bump(Bs)],
        bumps(Ds, I, T).
bumps([D|Ds0], I0, T) -->
        { D #=< T,
          I #= I0 + 1 },
        bumps(Ds0, I, T).


bump(D, T, Ds0, Ds, I0, I) --> [I0-D],
        { I1 #= I0 + 1 },
        run(Ds0, Ds, T, I1, I).

run([], [], _, I, I) --> [].
run([D|Ds0], Ds, T, I0, I) --> [I0-D],
        { D #> T,
          I1 #= I0 + 1 },
        run(Ds0, Ds, T, I1, I).
run([D|Ds0], [D|Ds0], T, I, I) -->
        { D #=< T }.

示例查询和答案:

? -  data_threshold_bumps([3,6,7,8,2,4,5,6,9,4,7,3],5,Bs)。
Bs = [bump([2-6,3-7,4-8]),bump([8-6,9-9]),bump([11-7])] ;
假。

请注意,事实并非如此 相当 您需要的完全相同的数据表示,但将它转换为那个是微不足道的。

以下是一些改进此解决方案的想法,从更容易到更难:

  • 使用,摆脱不必要的选择点 if_/3
  • 使用DCG表示法真的有意义吗? bumps//3 和 run//5 在上面的代码?在这里使用DCG比常规谓词有什么好处和缺点?
  • 玩不同的问题视图:你能转​​动DCG视图吗?例如,如何描述实际情况 数据 使用DCG,而不是颠簸?
  • 在您发布的代码中追踪不需要的解决方案的来源。

顺便说一句,到 否定 一个(可再生的)CLP(FD)约束,你需要使用 (#/\)/2 表示连词。确实如此  与...合作 (,)/2


7
2017-07-23 18:05



你可能意味着 (',')/2 - false
谢谢你的解决方案。我的不需要的解决方案是否与我使用append有关?试着想一想你的想法:) - user27815
即使没有查看代码的细节,我也会这样说 append/3 绝对是其中之一 主要嫌疑人 在这种情况下产生的答案比我们想要的多。注意经常使用 append/3 几乎总是表明您的数据结构存在问题:您应该重写算法,以便始终可以推断列表的头部(例如: Ls = [First,Second|Rest]),或使用DCG更有效地描述列表。 - mat
就个人而言,当列表以某种方式涉及时,我几乎总是使用DCG表示法来描述它们,所以,可能是的。 - mat
再次感谢您的建议和专业知识。 - user27815


在下面的代码中,您将找到括号中的许多部分

:- if(false).
...
:- endif.

所有这些部分都得到了相同的结果

?- data_threshold_bumps([3,6,7,8,2,4,5,6,9,4,7,3], 5, Bs).
Bs = [bump([11], [7]), bump([8, 9], [6, 9]), bump([2, 3, 4], [6, 7, 8])] ;
false.

代码本身只是一个模式匹配的应用程序,从最后到第一个,显示了一种可能的方法来重构相同的基本bump / 5谓词以获得更好的可读性(但是,实际上,我的首选它是最后一个。 ..)

data_threshold_bumps(Es, T, Sorted) :-
    bumps(Es, 1, T, Bs),
    predsort(by_len, Bs, Sorted).

bumps([], _, _, []).
bumps([E|Es], P, T, Bs) :-
    succ(P, Q),
    bumps(Es, Q, T, Cs),
    bump(E, P, T, Cs, Bs).

by_len(<, bump(Xs,_), bump(Ys,_)) :-
    length(Xs, Xl),
    length(Ys, Yl), Xl < Yl.
by_len(>, _, _).

:- use_module(library(clpfd)).

bump(E, _, T, Bs, Bs) :- E #=< T.
bump(E, P, T, Cs, Bs) :- E #> T, elem_placed(E, P, Cs, Bs).

elem_placed(E, P, [], [bump([P], [E])]).
elem_placed(E, P, [X|Bs], [Y|Bs]) :-
    X = bump([Q|Ps], [F|Es]),
    P #= Q-1,
    Y = bump([P,Q|Ps], [E,F|Es]).
elem_placed(E, P, [X|Bs], [bump([P],[E]), X|Bs]) :-
    X = bump([Q|_Ps], _Es),
    P #\= Q-1.

:- if(false).

bump(E, _, T, Bs, Bs) :- E =< T.
bump(E, P, T, Cs, Bs) :- E > T, elem_placed(E, P, Cs, Bs).

% first stored: tail
elem_placed(E, P, [], [bump([P], [E])]).
% extend current
elem_placed(E, P, [X|Bs], [Y|Bs]) :-
    X = bump([Q|Ps], [F|Es]),
    succ(P, Q),
    Y = bump([P,Q|Ps], [E,F|Es]).
% place new
elem_placed(E, P, [X|Bs], [bump([P],[E]), X|Bs]) :-
    X = bump([Q|_Ps], _Es),
    \+ succ(P, Q).

:- endif.

:- if(false).

bump(E, _, T, Bs, Bs) :- E =< T.
bump(E, P, T, Cs, Bs) :- E > T, enabled(E, P, Cs, Bs).

enabled(E, P, [], [bump([P], [E])]).
enabled(E, P, [bump([Q|Ps], [F|Es])|Bs], [bump([P,Q|Ps], [E,F|Es])|Bs]) :- succ(P, Q).
enabled(E, P, [bump([Q|Ps], [F|Es])|Bs], [bump([P],[E]), bump([Q|Ps],[F|Es])|Bs]) :- \+ succ(P, Q).

:- endif.

:- if(false).

bump(E, _, T, Bs, Bs) :- E =< T.
bump(E, P, T, [], [bump([P], [E])]) :- E > T.
bump(E, P, T, [bump([Q|Ps], [F|Es])|Bs], [bump([P,Q|Ps], [E,F|Es])|Bs]) :- E > T, succ(P, Q).
bump(E, P, T, [bump([Q|Ps], [F|Es])|Bs], [bump([P],[E]), bump([Q|Ps],[F|Es])|Bs]) :- E > T, \+ succ(P, Q).

:- endif.

2
2017-07-30 09:10



巧妙地使用条件编译指令。 - Paulo Moura