I have a predicate that finds the correct solution but then goes on to find solutions which are not right.
?- 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
The idea is that it will find all the nonredundant bumps in the data, where a bump is a consecutive sublist of data
that is above threshold
, Returning an ordered (by size) list of bump/2s
where the first arg of bump/2 is a list of indicies from data and the second arg is the list of values. So bump([2, 3, 4], [6, 7, 8])
means that in data indices 2,3 and 4 are above 5, they are 6,7,8.
How do I add conditions so that these extra solutions are not found? -Without using once/1
.
If my code could be streamlined in other ways please let me know. It seems a little complicated for what it is trying to do.
So:
Here is my 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).
My impression is that you are overthinking this slightly. There is a straight-forward formulation for runs of numbers that exceed the threshold, which can be defined by considering the elements from first to last in a single traversal of the list. In particular, we do not need append/3
to do this.
Always consider using DCG notation (dcg) when describing lists in Prolog. In this case, it takes a moment of reflection to decide how to best apply DCGs, because we are describing two lists:
However, excepting a few tricks and extensions, a DCG essentially only lets us describe a single list, not separate lists at the same time. So, we have this powerful and likely very suitable mechanism at our disposal, and must choose for which kind of list we want to apply it primarily.
In the following, I show a solution that uses a DCG to describe a list of bump/1 terms, that is, I "dedicate" the mechanism to describe the first kind of lists mentioned above, and use another DCG to describe the second kind of list, which I invoke via phrase/2
from within the first 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 }.
Example query and answer:
?- 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.
Note that this is not quite the exact same data representation that you need, but it is trivial to convert it to that one.
Here are a few ideas to improve upon this solution, from easier to harder:
if_/3
.bumps//3
and run//5
in the code above? What are the benefits and drawbacks of using DCGs here over regular predicates?By the way, to negate a (reifiable) CLP(FD) constraint, you need to use (#/\)/2
to denote a conjunction. It does not work with (,)/2
.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With