Grouping list elements based on values in list - list

i have a list of elements(tuples):
tuples(
[
(a,b,[1,3,5,7]),
(a,b,[9,11,13,15]),
(a,b,[17,19,21,23]),
(c,d,[0,2,4,6]),
(c,d,[8,10,12,14]),
(c,d,[16,18,20,22]),
(e,f,[100,200,300,400]),
(e,f,[500,600,700,800]),
(e,f,[900,1000,1100,1200])
]
).
How to group them so it becomes:
[
(a,b,[1,3,5,7,9,11,13,15,17,19,21,23]),
(c,d,[0,2,4,6,8,10,12,14,16,18,20,22]),
(e,f,[100,200,300,400,500,600,700,800,900,1000,1100,1200])
]
As we can see, we grouped the (a,b) (c,d) (e,f) and concatenated their respective lists.
thank you for the help.

How about this somewhat SQL-ish way:
Define a predicate to access data in the original deep and nasty datastructure (which uses conjunction (_,_) to create what looks like n-tuples but are actually "nearly" lists, except at the final position
of the backbone). On backtracking, it will pull out the individual
records one by one and present the information therein in the head variables:
some_tuple(V,W,Values) :-
tuples(Tuples),
member((V,W,Values), Tuples).
And then collect using a 2-level bagof/3 call.
solution(Bag) :-
bagof((V,W,FlatBagForVW), % will backtrack over V,W
SubBag^(bagof(L,some_tuple(V,W,L),BagForVW), % collect lists for a given V,W
flatten(BagForVW,FlatBagForVW)), % flatten it
Bag). % what we want
Done!
If you are in SWI-Prolog, first tell the toplevel printer to not elide long lists so much:
?-
set_prolog_flag(answer_write_options,[max_depth(100)]).
Then:
?-
solution(Bag).
Bag = [(a,b,[1,3,5,7,9,11,13,15,17,19,21,23]),
(c,d,[0,2,4,6,8,10,12,14,16,18,20,22]),
(e,f,[100,200,300,400,500,600,700,800,900,1000,1100,1200])].

A variation using foldl/4 and then library(yall):
'Grouping list elements based on values in list'(Gs) :-
tuples(Ts),
foldl([(X,Y,L),V0,V1]>>(
( append(N,[(X,Y,L0)|M],V0)
-> append(L0,L,L1)
; N=V0, L1=L
),
append(N,[(X,Y,L1)|M],V1)
)
,Ts,[],Gs).
a day after...
There is a bug going unnoticed, namely M remains unbound where a pair of keys (that is, X,Y in a tuple) is not present in V0 (have attempted to keep the variables naming coherent to the docs for foldl/4). A possible correction, that illustrates a single unification call (=/2) to perform multiple 'assignments' at once:
...
foldl([(X,Y,L),V0,V1]>>(
( append(N,[(X,Y,L0)|M],V0)
-> append(L0,L,L1)
; (N,M,L1)=(V0,[],L1)
),
append(N,[(X,Y,L1)|M],V1)
...
Still, it's not clear to me why the bug didn't materialized... for instance, here it's clearly visible...
?- append([1,2,3],[4,5,6|_],R).
R = [1, 2, 3, 4, 5, 6|_19156].
another way...
library(solution_sequences) is a recent addition to SWI-Prolog arsenal, providing more 'SQL like' constructs, for instance group_by/4:
by_group_by(Gs) :-
tuples(Ts),
findall((X,Y,All_xy), (
group_by([X,Y],L,member((X,Y,L),Ts),Lt),
append(Lt,All_xy)
),Gs).
The documentation is too much terse, but overall, the library is worth a try. There are some examples posted in SWI-Prolog discourse group, but I find the data used there boring and difficult to understand.
Note: I used the syntax [X,Y] for the free variables, to make clear the 'shape' of this important specification is unrelated to the pattern.

First we need to be able to find the list of unique A,B pairings in the list of tuples:
foo(X,A,B) :-
setof( p(A,B), C^member( (A,B,C), X ), T),
member( p(A,B), T).
/* 48 ?- tuples(_X), foo(_X,A,B).
A = a,
B = b ;
A = c,
B = d ;
A = e,
B = f. */
Next we collect the tuples for each pair of the A and B values:
bar(X,A,B,G) :-
foo(X,A,B), % for each unique (A,B,_) in X
findall( C, % find all Cs such that (A,B,C) is in X
member( (A,B,C), X),
CS),
append( CS,G). % and append them together
/* 66 ?- tuples(_X), bar(_X,A,B,G).
A = a,
B = b,
G = [1, 3, 5, 7, 9, 11, 13, 15, 17, 19, 21, 23] ;
A = c,
B = d,
G = [0, 2, 4, 6, 8, 10, 12, 14, 16, 18, 20, 22] ;
A = e,
B = f,
G = [100, 200, 300, 400, 500, 600, 700, 800, 900, 1000, 1100, 1200].*/
So that the grouping is done with
groups(X,GS):-
findall( (A,B,G), bar(X,A,B,G), GS).
/* 68 ?- tuples(_X), groups(_X, GS).
GS = [(a, b, [1, 3, 5, 7, 9, 11, 13, 15, 17, 19, 21, 23]),
(c, d, [0, 2, 4, 6, 8, 10, 12, 14, 16, 18, 20, 22]),
(e, f, [100, 200, 300, 400, 500, 600, 700, 800,
900, 1000, 1100, 1200])].
*/
update: from David Tonhofer's answer, we see that it can be done with just one nested bagof call,
solution( Sol ) :-
tuples(TS),
bagof( (A,B,FLS), % (* collect (A,B,FLS) for each (A,B) *)
LS^( % (* such that (A,B,L) is in TS *)
bagof( L, member((A,B,L), TS), LS ),
flatten( LS, FLS)
), % (* with the lists LS flattened *)
Sol ).
The outer bagof's goal predicate (i.e. the inner bagof call) is automatically backtracking to produce its LS result for each distinct pair of the A,B values, automagically achieving the same effect as we had "manually", in this answer.

group([],L,L).
group([(A,B,L)|T],Acc,Out):-
( append(L1,[(A,B,LL)|L2], Acc)
-> append(LL,L,LLL),
append(L1,[(A,B,LLL)|L2], NewAcc),
group(T,NewAcc,Out)
; append(Acc,[(A,B,L)],NewAcc),
group(T,NewAcc,Out)
).
?- tuples(L), group(L,[],G).
G = [
(a,b,[1, 3, 5, 7, 9, 11, 13, 15, 17, 19, 21, 23]),
(c,d,[0, 2, 4, 6, 8, 10, 12, 14, 16, 18, 20, 22]),
(e,f,[100, 200, 300, 400, 500, 600, 700, 800, 900, 1000, 1100, 1200])
],
L = [
(a,b,[1, 3, 5, 7]),
(a,b,[9, 11, 13, 15]),
(a,b,[17, 19, 21, 23]),
(c,d,[0, 2, 4, 6]),
(c,d,[8, 10, 12, 14]),
(c,d,[16, 18, 20, 22]),
(e,f,[100, 200, 300, 400]),
(e,f,[500, 600, 700, 800]),
(e,f,[900, 1000, 1100, 1200])
].
Basically I'm stripping an element from the (tuple) list ([(A,B,L)|T]) and look if I got a similar entry within my bag-list (2nd argument, append(L1,[(A,B,LL)|L2], Acc)). I use append/3 to do so because it can be used to find an element and at the same time dividing the original list into the list before and after the found element.
If I found an entry in the baglist, I append the two number lists (L and LL) to a new one (LLL) and exchange the values within the bag-list. Then I call the predicate again with the rest list and the altered bag-list.
If no element fits, I just add the element to the bag-list (as last element, append(Acc,[(A,B,L)],Acc2)) and call the predicate again. So each time I call the predicate group/3 it's first argument loses an element. Until there is no element left (group([],L,L).), in this case I state my bag-list is my ouput.
After playing a bit around with group_by/4 and/or bagof/3 as suggested by Guy coder, and using a variant of Davids "extraction" predicate here is another solution:
one_tuple(V,W,Value) :-
tuples(Tuples),
member((V,W,Values), Tuples),
member(Value, Values).
?- findall((A,B,Cs), bagof(C, one_tuple(A, B, C), Cs), O).
O = [(a,b,[1,3,5,7,9,11,13,15,17,19,21,23]),
(c,d,[0,2,4,6,8,10,12,14,16,18,20,22]),
(e,f,[100,200,300,400,500,600,700,800,900,1000,1100,1200])].

Related

Nested if statements that return boolean in prolog

I want to compare two date structures that return true if the first date is earlier than the second one, and false otherwise.
The logic is simple.
Let the first date D1, and second date D2.
If year of D1 > year of D2, return false.
If year of D1 == year of D2, compare month.
If year of D1 < year of D2, return true.
This process is repeated till the comparison of seconds.
Sample code I tried:
date_earlier_than(date(SY, SM, SD, SH, SMm, SS, _, _, _),
date(EY, EM, ED, EH, EMm, ES, _, _, _)) :-
( SY > EY ->
fail
;
SY =:= EY ->
( SM > EM ->
fail
;
SM =:= EM ->
( SD > ED ->
fail
;
SD =:= ED ->
( SH > EH ->
fail
;
SH =:= EH ->
( SMm > EMm ->
fail
;
SMm =:= EMm ->
( SS >= ES ->
fail
;
true
)
;
true
)
;
true
)
;
true
)
;
true
)
;
true
).
This predicate always returns false whatever dates passed as arguments.
I don't know where it goes wrong, and even if I use trace to keep track of the process, the predicate immediately returns false after the execution.
UPDATE:
The sample code works as expected, but I did not use date/9 when I tested it, leading to failure.
Here's revised form:
date_earlier_than(date(SY, SM, SD, SH, SMm, SS, SOff, STZ, SDST),
date(EY, EM, ED, EH, EMm, ES, EOff, ETZ, EDST)) :-
Start = date(SY, SM, SD, SH, SMm, SS, SOff, STZ, SDST),
End = date(EY, EM, ED, EH, EMm, ES, EOff, ETZ, EDST),
Start #< End, !.
This is all completely unnecessary.
If you represent the date as a compound term, those will compare correctly using the built-in comparison predicates and the "standard order of terms". See for example the SWI-Prolog docs:
https://www.swi-prolog.org/pldoc/man?section=standardorder
or GNU-Prolog:
http://www.gprolog.org/manual/gprolog.html#sec77
Try, for example:
?- date(2020, 10, 26, 10, 34, 43) #< date(2020, 10, 26, 6, 34, 43).
or:
?- date(2020, 10, 26, 10, 34, 43) #> date(2020, 10, 26, 6, 34, 43).
But this is also not necessary. Just represent your time as a timestamp (seconds since 1970-01-01T0:0:0Z, for example) and compare those as numbers (probably floats). See for example here:
https://www.swi-prolog.org/pldoc/man?section=timedate
This predicate always returns false whatever dates passed as arguments.
Not for me:
?- Today = date(2020, 10, 26, 12, 13, 14, _, _, _), Agincourt = date(1415, 10, 25, 09, 10, 11, _, _, _), date_earlier_than(Today, Agincourt).
false.
?- Today = date(2020, 10, 26, 12, 13, 14, _, _, _), Agincourt = date(1415, 10, 25, 09, 10, 11, _, _, _), date_earlier_than(Agincourt, Today).
Today = date(2020, 10, 26, 12, 13, 14, _2890, _2892, _2894),
Agincourt = date(1415, 10, 25, 9, 10, 11, _2916, _2918, _2920).
The battle of Agincourt did indeed take place before today, so your predicate seems to be working, at least to some extent. This is a good argument for always (always) including your test data in your questions.
Other than that, I agree with the other answer's suggestion of setting your data up such that you can just use #< to compare them. I don't necessarily agree with the other answer's suggesion of using an opaque seconds-since-epoch representation. It depends on what you actually need to do, and if it has to take time zones into account.

Enumerate non-1 step in Power M List

I know there is enumeration in list of Power M
for {1, 2, 3, ... 10} can be achieved by
{1..25}
What about {0, 25, 50, ... 250}
how can i enumerate every 25?
You can go with:
List.Generate(() => 0, each _ > 250, each _ +25)

Replacing successive decreasing numbers by the last number of the sequence in Prolog

I've been trying to solve this problem for quite sometime and I think the logic I'm attempting is flawed.
The objective is to replace a subsequently decreasing sublist of numbers by the last of the sublist.
?- compare([1, 3, 7, 6, 5, 10, 9], Result).
Result = [1, 3, 5, 9] ;
false.
What I tried was:
compare([A,B|T],X):-
%succ(B,A),
A is B+1,
append([],NextX,X),
compare([B|T],NextX).
remove([A,B|T],X):-
A=\=B+1,
compare([B|T],X).
I'm not certain how to write the base case for the compare/2 and I think the I'm not correctly converting my logic into the code. What I'm trying here is to compare A and B and drop A from the list if they are successive numbers.
Your help is very much appreciated.
You are almost there. First cover the special case: If the list contains only one element it is in the list.
compare([X],[X]).
your second rule just needs little altering:
compare([A,B|T],X):- % A is not in the list if
A is B+1, % A = B+1
compare([B|T],X). % Note: X is the same as in head of rule
Your predicate remove/2 is should be the 3rd rule of compare/2 covering the alternative case:
compare([A,B|T],[A|X]):- % A is in the list
A=\=B+1, % if A is not B+1
compare([B|T],X).
Now the query works:
?- compare([1, 3, 7, 6, 5, 10, 9], Result).
Result = [1,3,5,9] ?
yes
However, this predicate only works if the first list is variable free. You can't use it the other way round:
?- compare([A,B,C], [1,2]).
ERROR at clause 2 of user:compare/2 !!
INSTANTIATION ERROR- X is A+B: expected bound value
If you use library(clpfd) on the other hand ...
:- use_module(library(clpfd)).
compare([X],[X]).
compare([A,B|T],X):-
A #= B+1,
compare([B|T],X).
compare([A,B|T],[A|X]):-
A #\= B+1,
compare([B|T],X).
... the above query works too:
?- compare([A,B,C], [1,2]).
A = C = 2,
B = 1 ? ;
A = 1,
B = 3,
C = 2 ? ;
no

Sum up a list using Prolog

I want to sum all list elements greater than some given number. Here's the description:
sumup(L, N, GREATN, GEN) sums up the members of list L which are greater than GREATN to a variable N and puts these members into the list GEN.
Sample query:
?- sumup([8, 6, 10, 3, 9, 12], N, 7, GEN).
GEN = [8, 10, 9, 12], % expected answer
N = 39. % 8+10+9+12 = 39
Following is my code:
sum_list([], 0).
sum_list([H|T], Sum) :-
H > 3,
sum_list(T, Rest),
Sum is H + Rest.
sum_list([H|T], Sum) :-
H < 3,
write('').
I've tried the recursive way but I failed. How can I fix it?
Looking at your question and your code, I noticed a few things:
While you speak of "numbers" several times, your samples are integer-only. May we neglect non-integer numbers (float, rational) and handle integers only? I guess so.
There is an auto-loaded SWI-Prolog library(lists) predicate sum_list/2.
Calling your predicate sum_list/2 is an unfortunate choice.
Let's pick another name!
Your definition of sum_list/2 comprises three clauses:
sum_list([], 0).
Okay!
sum_list([H|T], Sum) :- H > 3, sum_list(T, Rest), Sum is H + Rest.
Notice H > 3? Why hardcode the constant integer 3?
sum_list([H|T], Sum) :- H < 3, write('').
That clause is not recursive. We need to see all list elements to calculate the sum, not stop at the first list element H that fulfills H < 3!
What's the use of write('')? I don't see any.
What good is the goal H < 3? Like above, why hardcode the integer 3?
Clause #2 covers H > 3. Clause #3 covers H < 3. What about H = 3?
In this answer we use clpfd, which is present in swi-prolog.
Here's a straight-forward definition of sumup/4 based on clpfd. While it could be improved in several ways (better determinism, accumulator-style, possibly some clever redundant constraints could also help), but for the time being it's a nice first shot:
:- use_module(library(clpfd)).
sumup([], 0, _, []).
sumup([Z|Zs], S0, P, [Z|Xs]) :-
Z #> P,
S0 #= S+Z,
sumup(Zs, S, P, Xs).
sumup([Z|Zs], S, P, Xs) :-
Z #=< P,
sumup(Zs, S, P, Xs).
Sample query as given by the OP:
?- sumup([8,6,10,3,9,12], N, 7, GEN).
N = 39, GEN = [8,10,9,12] % expected answer
; false. % leftover useless choicepoint
No need to write recursive code! Just use tfilter/3, (#<)/3, and clpfd:sum/3 like this:
:- use_module(library(clpfd)).
sumup(Zs, S, P, Xs) :-
tfilter(#<(P), Zs, Xs),
sum(Xs, #=, S).
Sample query:
?- sumup([8,6,10,3,9,12], S, 7, Xs).
S = 39, Xs = [8,10,9,12]. % expected result
Note that above query succeeds deterministically—a clear improvement over this previous answer!
Bonus! As the implementation of sumup/4 is monotonic, we know that the solution of above query is also part of the solution set of every generalization of the query. Look for yourself!
?- sumup([8,6,10,3,9,12], S, E, Xs).
S = 48, E in inf..2 , Xs = [8,6,10,3,9,12]
; S = 45, E in 3..5 , Xs = [8,6,10, 9,12]
; S = 39, E in 6..7 , Xs = [8, 10, 9,12] % <==== solution of above query
; S = 31, E in 8..8 , Xs = [10, 9,12]
; S = 22, E in 9..9 , Xs = [10, 12]
; S = 12, E in 10..11 , Xs = [12]
; S = 0, E in 12..sup, Xs = []
; false.
In SWI-Prolog you can use a fold and simply query:
L=[8, 6, 10, 3, 9, 12], include(<(7),L,Gen), foldl(plus,Gen,0,N).
so that sumup would be written as
sumup(L,N,GreatN,Gen) :-
include(<(GreatN),L,Gen),
foldl(plus,Gen,0,N).
plus/3 is an arithmetic predicate that works well in our case.

SICStus Prolog: How to permute the list [0,1,2,3,4,5,6,7,8,9]

I am new to Prolog and I'm trying out list permutation predicates.
Most of them take two arguments (e.g., permutation/2).
I'm looking to create one which only takes one argument (list) and also finds out if the list has exactly 10 elements.
So for example:
| ?- permutation([7, 1, 2, 3, 4, 5, 6, 0, 8, 9]).
yes
| ?- permutation(X).
X = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9];
...
| ?- permutation([A,B,C,D,E,F,G,H,I,J]).
A = 0
B = 1
C = 2
...
J = 9 ;
Appreciate any tips!
Work smarter, not harder:
Use clpfd!
:- use_module(library(clpfd)).
Using length/2, domain/2, all_different/1, and labeling/2 we define:
perm10(Zs) :-
length(Zs,10),
domain(Zs,0,9),
all_different(Zs),
labeling([],Zs).
Consider the goal gen_perm([8,0,1,2,3,4,5,6,7,8]).
We expect1 it to fail, and, in fact, it does...
... but how much work is being performed executing above goal?
Let's measure runtimes2 using call_time/2!
?- use_module(library(between),[repeat/1]).
true.
?- _Zs = [8,0,1,2,3,4,5,6,7,8], call_time((repeat(1000),gen_perm(_Zs);true),T_us).
T_us = 21940.
?- _Zs = [8,0,1,2,3,4,5,6,7,8], call_time((repeat(1000),perm10(_Zs) ;true),T_us).
T_us = 10.
Footnote 1: There are only 8 different integers in the list, so it cannot be a permutation of all integers between 0 and 9.
Footnote 2: Using SICStus Prolog version 4.3.2, x86_64-linux-glibc2.12.
Ok, thanks for the replies! This works:
takeout(X,[X|R],R).
takeout(X,[F|R],[F|S]) :-
takeout(X,R,S).
perm([X|Y],Z) :-
perm(Y,W),
takeout(X,Z,W).
perm([],[]).
gen_perm(List) :-
perm([0,1,2,3,4,5,6,7,8,9],List),
length(List,10).