Reputation: 150
I need a predicate to return a list with all combinations of the input list, and the list result size is in the second param, the predicate would be like this
permutInListN( +inputList, +lengthListResult, -ListResult),
example:
permutInListN([1,2,3],2,L).
? L=[1,2].
? L=[2,1].
? L=[1,3].
? L=[3,1].
? L=[2,3].
? L=[3,2].
Combinations of [1,2,3]
in a list L
with length 2
.
with no repetitions maybe using setoff.
this is my code but it doesn't work at all , no generate all solutions
permutInListN(_, 0, []).
permutInListN([X|Xs], N, [X|Ys]) :- N1 is N-1, permutInListN(Xs,N1,Ys).
permutInListN([_|Xs], N, Y) :- N>0, permutInListN(Xs,N,Y).
?permutInListN([1,2,3],2,L).
L = [1, 2]
L = [1, 3]
L = [2, 3]
thanks in advance.
Upvotes: 5
Views: 1752
Reputation: 24976
What you want is a combination followed by a permutation.
For combination:
comb(0,_,[]).
comb(N,[X|T],[X|Comb]) :-
N>0,
N1 is N-1,
comb(N1,T,Comb).
comb(N,[_|T],Comb) :-
N>0,
comb(N,T,Comb).
Example:
?- comb(2,[1,2,3],List).
List = [1, 2] ;
List = [1, 3] ;
List = [2, 3] ;
false.
For Permutation just use SWI-Prolog permutation/2
in library lists
:- use_module(library(lists)).
?- permutation([1,2],R).
R = [1, 2] ;
R = [2, 1] ;
false.
Putting them together
comb_perm(N,List,Result) :-
comb(N,List,Comb),
permutation(Comb,Result).
With your query
?- comb_perm(2,[1,2,3],R).
R = [1, 2] ;
R = [2, 1] ;
R = [1, 3] ;
R = [3, 1] ;
R = [2, 3] ;
R = [3, 2] ;
false.
Modified for your predicate
permutInListN(List,N,Result) :-
comb(N,List,Comb),
permutation(Comb,Result).
Example
?- permutInListN([1,2,3],2,R).
R = [1, 2] ;
R = [2, 1] ;
R = [1, 3] ;
R = [3, 1] ;
R = [2, 3] ;
R = [3, 2] ;
false.
Upvotes: 5
Reputation: 477170
Your permutInListN/3
predicate basically takes N
elements in an ordered way from the given list, but the order of the elements that are picked, is the same as the original order.
We can thus post-process this list, by finding all permutations of the selected elements, so something like:
permutInListN(L, N, R) :-
takeN(L, N, S),
permutation(S, R).
with takeN/3
almost equivalent to the predicate you defined:
takeN(_, 0, []).
takeN([X|Xs], N, [X|Ys]) :-
N > 0,
N1 is N-1,
takeN(Xs,N1,Ys).
takeN([_|Xs], N, Y) :-
N > 0,
takeN(Xs,N,Y).
permutation/3
[swi-doc] is a predicate from the lists
library [swi-doc].
select/3
sWe can also solve the problem by N
times using the select/3
predicate [swi-doc]. select(X, L, R)
takes an element X
from a list, and R
is a list, without that element. We can thus recursively pass the list and each time remove an element, until we removed N
elements, like:
permutInListN(_, 0, []).
permutInListN(L, N, [X|T]) :-
N > 0,
N1 is N-1,
select(X, L, R),
permutInListN(R, N1, T).
Upvotes: 1