Ich habe ein Prädikat, das die richtige Lösung findet, aber dann geht es weiter, um Lösungen zu finden, die nicht richtig sind.Entfernen Sie falsche nachfolgende Lösungen ohne einmal
?- 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])] ;
etc
Die Idee ist, dass sie alle nicht redundanten Beulen in den Daten zu finden, wo eine Beule ein konsekutiver sublist von data
ist, die über threshold
ist, Return eine geordnete (nach Größe) Liste bump/2s
, wobei das erste Argument von bump/2 eine Liste von Indizes aus Daten und das zweite arg die Liste von Werten ist. So bedeutet bump([2, 3, 4], [6, 7, 8])
, dass in Datenindizes 2,3 und 4 über 5 sind, sind sie 6,7,8.
Wie füge ich Bedingungen hinzu, damit diese zusätzlichen Lösungen nicht gefunden werden? -ohne Verwendung once/1
.
Wenn mein Code auf andere Arten optimiert werden könnte, lassen Sie es mich bitte wissen. Es scheint ein wenig kompliziert für das, was es versucht zu tun.
So:
Hier ist mein Code:
:-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).
Vermutlich meinst du '(',')/2' – false
Danke für die saubere Lösung. Sind meine unerwünschten Lösungen mit meiner Verwendung von append zu tun? Versuche, über deine Ideen nachzudenken :) – user27815
Auch ohne in die Details deines Codes geschaut zu haben, würde ich sagen, dass "append/3" definitiv zu den * Hauptverdächtigen * gehört, mehr Antworten zu generieren als wir in diesem Fall wollen. Beachten Sie, dass häufige Verwendung von 'append/3' fast immer ein Problem mit Ihren Datenstrukturen anzeigt: Sie sollten Ihren Algorithmus entweder neu schreiben, so dass Sie immer über den Kopf Ihrer Listen nachdenken können (Beispiel:' Ls = [First, Second | Rest ] '), oder verwenden Sie DCGs, um Listen effizienter zu beschreiben. – mat