一次删除不正确的后续解决方案
Remove incorrect subsequent solutions without once
我有一个谓词可以找到正确的解决方案,但随后继续寻找不正确的解决方案。
?- 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
其中 bump/2 的第一个参数是数据中的索引列表,第二个参数是值列表。所以 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).
我的印象是你有点想多了。对于超过阈值的 runs 的数字,有一个简单的公式,可以通过考虑列表的单次遍历中从头到尾的元素来定义。特别是,我们不需要 append/3
来做到这一点。
在 Prolog 中描述 lists 时,始终考虑使用 DCG 表示法 (dcg)。在这种情况下,需要花点时间思考如何最好地应用 DCG,因为我们正在描述 两个 列表:
- 运行列表(超过阈值的连续元素)
- 在运行中,索引和值.
的列表
然而,除了一些技巧和扩展之外,DCG 本质上只能让我们描述一个 单个 列表,而不是同时描述多个单独的列表。因此,我们拥有这个强大且可能非常合适的机制供我们使用,并且必须选择我们要将其应用到哪种列表主要。
在下面,我展示了一个使用DCG来描述bump/1项列表的解决方案,即我"dedicate"机制描述上面提到的第一种列表,并使用另一个 DCG 来描述 second 类型的列表,我通过 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])] ;
false.
请注意,这完全与您需要的数据表示形式完全相同,但将其转换为那种数据表示形式很简单。
这里有一些改进此解决方案的想法,从易到难:
- 去掉不必要的选择点,使用
if_/3
。
- 在上面的代码中对
bumps//3
和 run//5
使用 DCG 符号真的有意义吗?与常规谓词相比,在这里使用 DCG 有哪些优点和缺点?
- 玩转问题的不同视角:你能把 DCG 视角调过来吗?例如,用 DCG 而不是颠簸来描述实际的 数据 怎么样?
- 追踪您发布的代码中不需要的解决方案的来源。
顺便说一句,要否定一个(可具体化的)CLP(FD)约束,您需要使用(#/\)/2
来表示一个连词。它 不 与 (,)/2
一起工作。
在下面的代码中,您会发现许多部分被
括起来
:- 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.
我有一个谓词可以找到正确的解决方案,但随后继续寻找不正确的解决方案。
?- 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
其中 bump/2 的第一个参数是数据中的索引列表,第二个参数是值列表。所以 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).
我的印象是你有点想多了。对于超过阈值的 runs 的数字,有一个简单的公式,可以通过考虑列表的单次遍历中从头到尾的元素来定义。特别是,我们不需要 append/3
来做到这一点。
在 Prolog 中描述 lists 时,始终考虑使用 DCG 表示法 (dcg)。在这种情况下,需要花点时间思考如何最好地应用 DCG,因为我们正在描述 两个 列表:
- 运行列表(超过阈值的连续元素)
- 在运行中,索引和值. 的列表
然而,除了一些技巧和扩展之外,DCG 本质上只能让我们描述一个 单个 列表,而不是同时描述多个单独的列表。因此,我们拥有这个强大且可能非常合适的机制供我们使用,并且必须选择我们要将其应用到哪种列表主要。
在下面,我展示了一个使用DCG来描述bump/1项列表的解决方案,即我"dedicate"机制描述上面提到的第一种列表,并使用另一个 DCG 来描述 second 类型的列表,我通过 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])] ; false.
请注意,这完全与您需要的数据表示形式完全相同,但将其转换为那种数据表示形式很简单。
这里有一些改进此解决方案的想法,从易到难:
- 去掉不必要的选择点,使用
if_/3
。 - 在上面的代码中对
bumps//3
和run//5
使用 DCG 符号真的有意义吗?与常规谓词相比,在这里使用 DCG 有哪些优点和缺点? - 玩转问题的不同视角:你能把 DCG 视角调过来吗?例如,用 DCG 而不是颠簸来描述实际的 数据 怎么样?
- 追踪您发布的代码中不需要的解决方案的来源。
顺便说一句,要否定一个(可具体化的)CLP(FD)约束,您需要使用(#/\)/2
来表示一个连词。它 不 与 (,)/2
一起工作。
在下面的代码中,您会发现许多部分被
括起来:- 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.