Filter list in prolog - prolog

I'm trying to rewrite code from Haskell to Prolog.
count :: Eq a => a -> [a] -> Int
count x = length . filter (x==)
f :: [Integer] -> [Integer]
f [] = []
f list = filter (\x -> count x list == 1) list
This code return list that contains elements that appears only once in the list.
So if I have list [1,1,2,2,3,4,4,5] this function returns [3,5]
I tried to find filter construction in Prolog but seems there no such thing. How can I make similar function in Prolog ?

To the existing answers, I would like to add an answer that is quite general in the sense that you can use it in multiple directions.
Building block: list_element_number/3
I start with the following predicate, defining a relation between:
a list Ls0
an element E
the number N of occurrences of E in Ls0
Here it is:
list_element_number(Ls0, E, N) :-
tfilter(=(E), Ls0, Ls),
length(Ls, N).
This solution uses tfilter/3 from library(reif). The predicate subsumes the function count you have posted. The main benefit of this predicate over the function is that the predicate can be used not only in those cases that even Haskell can do easily, such as:
?- list_element_number([a,b,c], a, N).
N = 1.
No, we can use it also in other directions, such as:
?- list_element_number([a,b,c], X, 1).
X = a ;
X = b ;
X = c ;
false.
Or even:
?- list_element_number([a,b,E], X, 2).
E = X, X = a ;
E = X, X = b ;
false.
Or even:
?- list_element_number([A,B,C], X, 3).
A = B, B = C, C = X ;
false.
And even in the most general case, in which all arguments are fresh variables:
?- list_element_number(Ls, E, N).
Ls = [],
N = 0 ;
Ls = [E],
N = 1 ;
Ls = [E, E],
N = 2 ;
Ls = [E, E, E],
N = 3 .
We can fairly enumerate all answers like this:
?- length(Ls, _), list_element_number(Ls, E, N).
Ls = [],
N = 0 ;
Ls = [E],
N = 1 ;
Ls = [_160],
N = 0,
dif(E, _160) ;
Ls = [E, E],
N = 2 .
Main predicate: list_singletons/2
Using this building block, we can define list_singletons/2 as follows:
list_singletons(Ls, Singles) :-
tfilter(count_one(Ls), Ls, Singles).
count_one(Ls, E, T) :-
list_element_number(Ls, E, Num),
cond_t(Num=1, true, T).
This uses cond_t/3 and (again) tfilter/3 from library(reif).
Sample queries
Here are a few sample queries. First, the test case you have posted:
?- list_singletons([1,1,2,2,3,4,4,5], Singles).
Singles = [3, 5].
It works as desired.
Now a case involving variables:
?- list_singletons([A,B], Singles).
A = B,
Singles = [] ;
Singles = [A, B],
dif(A, B).
On backtracking, all possibilities are generated: Either A = B holds, and in that case, there is no element that occurs only once. Or A is different from B, and in that case both A and B occur exactly once.
As a special case of the above query, we can post:
?- list_singletons([A,A], Singles).
Singles = [].
And as a generalization, we can post:
?- length(Ls, _), list_singletons(Ls, Singles).
Ls = Singles, Singles = [] ;
Ls = Singles, Singles = [_7216] ;
Ls = [_7216, _7216],
Singles = [] ;
Ls = Singles, Singles = [_7828, _7834],
dif(_7828, _7834) ;
Ls = [_7216, _7216, _7216],
Singles = [] ;
Ls = [_7910, _7910, _7922],
Singles = [_7922],
dif(_7910, _7922) .
Enjoy the generality of this relation, obtained via logical-purity.

A more simple version :
filter_list(L,OutList):-findall(X, (select(X,L, L1),\+member(X, L1)) , OutList).
?- filter_list([1,1,2,2,3,4,4,5],L).
L = [3, 5].
Without findall, you can try
filter_list(In, Out) :- filter_list(In, _, Out).
filter_list([], [], []).
filter_list([H|T], L1, L2) :-
filter_list(T, LL1, LL2),
( member(H, LL1)
-> L1 = LL1, L2 = LL2
; (select(H, LL2, L2)
-> L1 = [H|LL1]
; L1 = LL1, L2 = [H|LL2])).

without counting...
filter_uniques([],[]).
filter_uniques([H|T],F) :-
delete(T,H,D),
( D=T -> F=[H|R],S=T ; F=R,S=D ),
filter_uniques(S,R).
a more direct rewrite of your code, with library(yall) support for inlining of the filter predicate (the first argument to include/3)
filt_uniq(L,F) :-
include({L}/[E]>>aggregate(count,member(E,L),1),L,F).

A simple version:
(see the comment by #false below, the version with findall/3 has some inconsistency problems in more complex queries but second version looks ok however it is definitely not so efficient ).
filter_list(L,OutList):-findall(X, (member(X,L),count(X,L,N),N=:=1) , OutList).
count(_,[],0).
count(X,[X|T],N):-count(X,T,N1),N is N1+1.
count(X,[X1|T],N):-dif(X,X1),count(X,T,N).
The predicate filter_list/2 uses findall/3 and simply states find all X that belong to the list L and count returns 1 and store them in OutList.
Example:
?- filter_list([1,1,2,2,3,4,4,5],L).
L = [3, 5].
You could write filter_list/2 without using findall/3 like:
filter_list(L,OutList):- filter_list(L,OutList,L).
filter_list([],[],_).
filter_list([H|T],[H|T1],L):-count(H,L,N), N=:=1, filter_list(T,T1,L).
filter_list([H|T],T1,L):-count(H,L,N), N > 1, filter_list(T,T1,L).

Related

Prolog delete an element into a given list

Hello I wish some advice or words about this task:
Define a statement with three parameters where the first one is a list, the second one is an element (atom or list) and the last one is a list which must accomplish it is equal to the first but first's list' elements which match second parameter,are gone.
Examples:
> elimina([f, e, d, [a, h], a, d, a], a, L)
L = [f, e, d, [a, h], d]
> elimina([f, e, d, [ a, h], a, [d, a]], [a, h], L)
L = [f, e, d, a, [d, a]]
I tried:
elimina([],_,[]).
elimina([X],X,[]).
elimina([X],Y,[X]).
elimina([H|T],H,Result) :-
elimina([T],H,Result).
elimina([H|T],Y,Result):-
elimina([T],H,Result).
I have the doubt about what to write when I shout the recursive call:
elimina([T],H,Result).
Because first I don't know how differently should be the behave when the input second element matchs the head rather than don't matching the head; so I put the same call.
Also I doubt because: Is really needed to put the base case: elimina([X],Y,[X]).? I thought we could pass the exercise with just matching the element to delete with the ones which are really into the list.
Thank you for your time.
There is a very general method how you can test your own code in Prolog. Simply ask Prolog to generate via the most general question all possibilities.
?- elimina([], D, Ys).
Ys = []. % 1: nice!
?- elimina([X], D, Ys).
D = X, Ys = [] % 1: nice!
; Ys = [X] % 2: lacks dif(X, D)
; X = [], D = [], Ys = [] % 3: correct but subsumed by 1
; D = X, Ys = [[]] % 4: incorrect
; X = [], D = [], Ys = [] % 5: correct but subsumed by 1
; X = [], D = [], Ys = [[]] % 6: incorrect
; X = [], D = [], Ys = [] % 7: correct but subsumed by 1
; ... .
For the empty list everything is fine. But for the one-element list, there are many superfluous answers! Actually, there should only be two answers:
D = X, Ys = []
; dif(D, X), Ys = [X].
So now pick some case you want to improve!
Maybe take answer #4 and set D = a, X = a:
?- elimina([a], a, Ys).
Ys = [] % 1: nice
; Ys = [a] % 2: incorrect
; Ys = [[]] % 3: incorrect
; Ys = [] % 4: correct but subsumed by 1
; Ys = [[]] % 5: incorrect and subsumed by 3
; Ys = [] % 6: correct but subsumed by 1
; ... .
So I will pick #3 which actually should fail, but does not
?- elimina([a],a,[[]]).
true
; true
; ... .
Narrow down the culprit by inserting false and some extra equations:
?- elimina([a],a,[[]]).
false.
elimina([],_,[]) :- false.
elimina([X],X,[]) :- false.
elimina([X],Y,[X]) :- Y = a, X = [].
elimina([H|T],H,Result) :- false,
elimina([T],H,Result).
elimina([H|T],Y,Result):- Result = [[]],
elimina([T],H,Result).
Now look at what is left and think about it. Should these remaining rules really hold?
In the remaining visible part there must be an error!
When describing lists, it's usually worthwhile to consider using DCGs for the task. You could describe the relation like so:
elimina(L1,X,L2) :- % L2 is described by
phrase(elimina_x(L1,X),L2). % elimina_x//2
elimina_x([],_X) --> % nothing to delete
[]. % from the empty list
elimina_x([X|Xs],X) --> % if the head of the list equals X
elimina_x(Xs,X). % it's not in the list, same for the tail
elimina_x([X|Xs],Y) --> % if the head of the list
{dif(X,Y)}, % differs from Y
[X], % it is in the list
elimina_x(Xs,Y). % same for the tail
Your example queries yield the desired result.
?- elimina([f, e, d, [a, h], a, d, a], a, L).
L = [f,e,d,[a,h],d] ? ;
no
?- elimina([f, e, d, [ a, h], a, [d, a]], [a, h], L).
L = [f,e,d,a,[d,a]] ? ;
no
Alternatively, you can also express this relation more compactly, using if_/3, (=)/3 and tfilter/3:
dif_t(X,Y,T) :-
if_(X=Y,T=false,T=true).
elimina(L1,X,L2) :-
tfilter(dif_t(X),L1,L2).
The above queries yield the same answers with this version.

Sum elements of list in prolog

I want to sum element of a list like this:
sum([1,[2,3],4],S).
I used that but I have a problem:
sum([],0).
sum([T|R],M) :- sum(R,S), M is T+S.
I get the following error:
ERROR: is/2: Type error: `[]' expected, found `[2,3]' (a list) ("x" must hold one character)
The problem is that you can't add T if T is a list. You could easily solve using is_list/1 that succeds if T is a list:
sum([],0).
sum([T|R],M) :- (is_list(T) -> sum(T,N1),sum(R,S), M is N1+S
; sum(R,S), M is T+S ).
Examples:
?- sum([1,[2,3],4],S).
S = 10.
?- sum([1,2,3,4],S).
S = 10.
?- sum([1,[2],[3],4],S).
S = 10.
?- sum([1,[[2],[3]],4],S).
S = 10.
A better approach would be using CLPFD:
:- use_module(library(clpfd)).
sum([],0).
sum([[]],0).
sum([T|R],M) :- (is_list(T) -> sum(T,N1),sum(R,S), M #= N1+S
; sum(R,S), M #= T+S ).
Now you can query more general questions like:
?- sum(L,N).
L = [],
N = 0 ;
L = [[]],
N = 0 ;
L = [N],
N in inf..sup ;
L = [N, []],
N in inf..sup ;
L = [_1836, _1842],
_1836+_1842#=N ;
L = [_1842, _1848, []],
_1842+_1848#=N ;
L = [_2142, _2148, _2154],
_2142+_2192#=N,
_2148+_2154#=_2192 ;
L = [_2148, _2154, _2160, []],
_2148+_2204#=N,
_2154+_2160#=_2204 ;
L = [_2448, _2454, _2460, _2466],
_2448+_2504#=N,
_2454+_2528#=_2504,
_2460+_2466#=_2528 ;
and goes on...
Another approach:
% Old code, with vars renamed:
%sum([], 0).
%sum([Num|Tail], TotalSum) :- sum(Tail, TailSum), TotalSum is Num + TailSum.
% New code:
sum([], 0).
sum([Elem|Tail], TotalSum) :-
sum(Elem, ElemSum),
sum(Tail, TailSum),
TotalSum is ElemSum + TailSum.
sum(Num, Num).
Demo: http://swish.swi-prolog.org/p/cmzcsXrJ.pl.
You can use flatten/2 plus foldl/4 or sum_list/2 library predicates in Swi-Prolog:
% flatten/2 + foldl/4 based implementation
sum_nested_list(List, Sum) :-
flatten(List, Flat),
foldl(plus, Flat, 0, Sum).
% flatten/2 + sum_list/2 based implementation
sum_nested_list(List, Sum) :-
flatten(List, Flat),
sum_list(Flat, Sum).

how to define the delete(X,L1,L2) relation using prolog where L2 is the resulted list in which item X is deleted from list L1

(1) how to define the delete(X,L1,L2) relation using Prolog where L2 is the resulted list in which item X is deleted from list L1
(2) How to draw the derivation tree to answer the following query?
| ?- delete(3,[4,10,6,8,1,3,9],L)
Save logical-purity by using the meta-predicate tfilter/3 and reified disequality dif/3:
?- tfilter(dif(3),[ 4, 10,6,8,1,3,9],[4,10,6,8,1,9]).
true.
?- tfilter(dif(3),[3,3,3,4,3,3,10,6,8,1,3,9],[4,10,6,8,1,9]).
true.
Note this works just as fine with non-ground terms, too!
?- tfilter(dif(Y),[A,B],Xs).
Xs = [ ], Y = A, A = B ;
Xs = [ B], Y = A, dif(A,B) ;
Xs = [A ], Y = B, dif(B,A) ;
Xs = [A,B], dif(Y,B), dif(Y,A).

Extracting sequences (Lists) Prolog

Given a list eg [1,2,3,7,2,5,8,9,3,4] how would I extract the sequences within the list?
A sequence is defined as an ordered list (Normally I would say n-tuple but I have been told in prolog a tuple is referred to as a sequence). So we want to cut the list at the point where the next element is smaller than the previous one.
So for the list [1,2,3,7,2,5,8,9,3,4] it should return:
[ [1,2,3,7], [2,5,8,9], [3,4] ] %ie we have cut the list at position 4 & 8.
For this exercise you CANNOT use the construct ; or ->
Many thanks in advance!
EXAMPLE RESULTS:
eg1.
?-function([1,2,3,7,2,5,8,9,3,4],X): %so we cut the list at position 4 & 9
X = [ [1,2,3,7], [2,5,8,9], [3,4] ].
eg2.
?-function([1,2,3,2,2,3,4,3],X): %so we cut the list at position 3,4 & 8
X = [ [1,2,3], [2], [2,3,4], [3] ].
Hopefully that helps clarify the problem. If you need further clarification just let me know! Thanks again in advance for any help you are able to provide.
First, let's break it down conceptually. The predicate list_ascending_rest/3 defines a relation between a list Xs, the left-most ascending sublist of maximum length Ys, and the remaining items Rest. We will use it like in the following query:
?- Xs = [1,2,3,7,2,5,8,9,3,4], list_ascending_rest(Xs,Ys,Rest).
Ys = [1,2,3,7],
Rest = [2,5,8,9,3,4] ;
false.
The straight-forward predicate definition goes like this:
:- use_module(library(clpfd)).
list_ascending_rest([],[],[]).
list_ascending_rest([A],[A],[]).
list_ascending_rest([A1,A2|As], [A1], [A2|As]) :-
A1 #>= A2.
list_ascending_rest([A1,A2|As], [A1|Bs], Cs) :-
A1 #< A2,
list_ascending_rest([A2|As], Bs,Cs).
Then, let's implement predicate list_ascendingParts/2. This predicate repeatedly uses list_ascending_rest/3 for each part until nothing is left.
list_ascendingParts([],[]).
list_ascendingParts([A|As],[Bs|Bss]) :-
list_ascending_rest([A|As],Bs,As0),
list_ascendingParts(As0,Bss).
Example queries:
?- list_ascendingParts([1,2,3,7,2,5,8,9,3,4],Xs).
Xs = [[1,2,3,7], [2,5,8,9], [3,4]] ;
false.
?- list_ascendingParts([1,2,3,2,2,3,4,3],Xs).
Xs = [[1,2,3], [2], [2,3,4], [3]] ;
false.
Edit 2015/04/05
What if the ascending parts are known but the list is unknown? Let's find out:
?- list_ascendingParts(Ls, [[3,4,5],[4],[2,7],[5,6],[6,8],[3]]).
Ls = [3,4,5,4,2,7,5,6,6,8,3] ? ;
no
And let's not forget about the most general query using list_ascendingParts/2:
?- assert(clpfd:full_answer).
yes
?- list_ascendingParts(Ls, Ps).
Ls = [], Ps = [] ? ;
Ls = [_A], Ps = [[_A]] ? ;
Ls = [_A,_B], Ps = [[_A],[_B]], _B#=<_A, _B in inf..sup, _A in inf..sup ? ...
Edit 2015-04-27
Room for improvement? Yes, definitely!
By using the meta-predicate splitlistIfAdj/3 one can "succeed deterministically" and "use non-determinism when required", depending on the situation.
splitlistIfAdj/3 is based on if_/3 as proposed by #false in this answer. So the predicate passed to it has to obey the same convention as (=)/3 and memberd_truth/3.
So let's define (#>)/3 and (#>=)/3:
#>=(X,Y,Truth) :- X #>= Y #<==> B, =(B,1,Truth).
#>( X,Y,Truth) :- X #> Y #<==> B, =(B,1,Truth).
Let's re-ask above queries, using splitlistIfAdj(#>=)
instead of list_ascendingParts:
?- splitlistIfAdj(#>=,[1,2,3,7,2,5,8,9,3,4],Pss).
Pss = [[1,2,3,7],[2,5,8,9],[3,4]]. % succeeds deterministically
?- splitlistIfAdj(#>=,[1,2,3,2,2,3,4,3],Pss).
Pss = [[1,2,3],[2],[2,3,4],[3]]. % succeeds deterministically
?- splitlistIfAdj(#>=,Ls,[[3,4,5],[4],[2,7],[5,6],[6,8],[3]]).
Ls = [3,4,5,4,2,7,5,6,6,8,3] ; % works the other way round, too
false. % universally terminates
Last, the most general query. I wonder what the answers look like:
?- splitlistIfAdj(#>=,Ls,Pss).
Ls = Pss, Pss = [] ;
Ls = [_G28], Pss = [[_G28]] ;
Ls = [_G84,_G87], Pss = [[_G84],[_G87]], _G84#>=_G87 ;
Ls = [_G45,_G48,_G41], Pss = [[_G45],[_G48],[_G41]], _G45#>=_G48, _G48#>=_G41
% and so on...
maplist/3 as suggested in the comment won't help you here because maplist/3 is good at taking a list and mapping each element into a same-size collection of something else, or establishing a relation evenly across all of the individual elements. In this problem, you are trying to gather contiguous sublists that have certain properties.
Here's a DCG solution. The idea here is to examine the list as a series of increasing sequences where, at the boundary between them, the last element of the prior sequence is less than or equal to the first element of the following sequence (as the problem statement basically indicates).
% A set of sequences is an increasing sequence ending in X
% followed by a set of sequences that starts with a value =< X
sequences([S|[[Y|T]|L]]) --> inc_seq(S, X), sequences([[Y|T]|L]), { X >= Y }.
sequences([S]) --> inc_seq(S, _).
sequences([]) --> [].
% An increasing sequence, where M is the maximum value
inc_seq([X,Y|T], M) --> [X], inc_seq([Y|T], M), { X < Y }.
inc_seq([X], X) --> [X].
partition(L, R) :- phrase(sequences(R), L).
| ?- partition([1,2,3,4,2,3,8,7], R).
R = [[1,2,3,4],[2,3,8],[7]] ? ;
(1 ms) no
| ?- partition([1,2,3,2,2,3,4,3],X).
X = [[1,2,3],[2],[2,3,4],[3]] ? ;
(1 ms) no
The only reason for the rule sequences([]) --> []. is if you want partition([], []) to be true. Otherwise, the rule isn't required.

Prolog, split list into two lists

I got a problem with lists. What I need to do is to split one list [1,-2,3,-4], into two lists [1,3] and [-2,-4]. My code looks like the following:
lists([],_,_).
lists([X|Xs],Y,Z):- lists(Xs,Y,Z), X>0 -> append([X],Y,Y) ; append([X],Z,Z).
and I'm getting
Y = [1|Y],
Z = [-2|Z].
What am I doing wrong?
If your Prolog system offers clpfd you could preserve logical-purity. Want to know how? Read on!
We take the second definition of lists/3 that #CapelliC wrote in
his answer as a starting point, and replace partition/4 by tpartition/4 and (<)/2 by (#<)/3:
lists(A,B,C) :- tpartition(#<(0),A,B,C).
Let's run a sample query!
?- As = [0,1,2,-2,3,4,-4,5,6,7,0], lists(As,Bs,Cs).
As = [0,1,2,-2,3,4,-4,5,6,7,0],
Bs = [ 1,2, 3,4, 5,6,7 ],
Cs = [0, -2, -4, 0].
As we use monotone code, we get logically sound answers for more general queries:
?- As = [X,Y], lists(As,Bs,Cs).
As = [X,Y], Bs = [X,Y], Cs = [ ], X in 1..sup, Y in 1..sup ;
As = [X,Y], Bs = [X ], Cs = [ Y], X in 1..sup, Y in inf..0 ;
As = [X,Y], Bs = [ Y], Cs = [X ], X in inf..0 , Y in 1..sup ;
As = [X,Y], Bs = [ ], Cs = [X,Y], X in inf..0 , Y in inf..0 .
Here you have. It splits a list, and does not matter if have odd or even items number.
div(L, A, B) :-
append(A, B, L),
length(A, N),
length(B, N).
div(L, A, B) :-
append(A, B, L),
length(A, N),
N1 is N + 1,
length(B, N1).
div(L, A, B) :-
append(A, B, L),
length(A, N),
N1 is N - 1,
length(B, N1).
Refer this:
domains
list=integer*
predicates
split(list,list,list)
clauses
split([],[],[]).
split([X|L],[X|L1],L2):-
X>= 0,
!,
split(L,L1,L2).
split([X|L],L1,[X|L2]):-
split(L,L1,L2).
Output :
Goal: split([1,2,-3,4,-5,2],X,Y)
Solution: X=[1,2,4,2], Y=[-3,-5]
See, if that helps.
Just for variety, this can also be done with a DCG, which is easy to read for a problem like this:
split([], []) --> [].
split([X|T], N) --> [X], { X >= 0 }, split(T, N).
split(P, [X|T]) --> [X], { X < 0 }, split(P, T).
split(L, A, B) :-
phrase(split(A, B), L).
As in:
| ?- split([1,2,-4,3,-5], A, B).
A = [1,2,3]
B = [-4,-5] ? ;
no
It also provides all the possible solutions in reverse:
| ?- split(L, [1,2,3], [-4,-5]).
L = [1,2,3,-4,-5] ? ;
L = [1,2,-4,3,-5] ? ;
L = [1,2,-4,-5,3] ? ;
L = [1,-4,2,3,-5] ? ;
L = [1,-4,2,-5,3] ? ;
L = [1,-4,-5,2,3] ? ;
L = [-4,1,2,3,-5] ? ;
L = [-4,1,2,-5,3] ? ;
L = [-4,1,-5,2,3] ? ;
L = [-4,-5,1,2,3] ? ;
(2 ms) no
Gaurav's solution will also do this if the cut is removed and an explicit X < 0 check placed in the third clause of the split/3 predicate.
There are several corrections to be done in your code.
If you enjoy compact (as readable) code, a possibility is
lists([],[],[]).
lists([X|Xs],Y,Z) :-
( X>0 -> (Y,Z)=([X|Ys],Zs) ; (Y,Z)=(Ys,[X|Zs]) ), lists(Xs,Ys,Zs).
But since (SWI)Prolog offers libraries to handle common list processing tasks, could be as easy as
lists(A,B,C) :- partition(<(0),A,B,C).

Resources