How to bound all combinations prolog search with clp(fd)? - prolog

The thing I wanted to do was generate all combinations of elements from a given list. E.g.: From [a,b,c], I might want:
[]
[a]
[b]
[c]
[a,a]
[a,b]
[a,c]
[b,a]
...
And so on. Perhaps there is a magical prolog one-liner that does this. If so, I would love to hear it.
However, my question is less about solving this particular problem and more of a request that someone explain some subtleties of Prolog's search algorithm for me.
So here's what I did first to solve the above problem:
members([], _).
members([X|Xs], List) :-
member(X,List),
members(Xs, List).
This works great but returns all possible results, and not in a great order:
[]
[a]
[a,a]
[a,a,a]
Okay, that's no problem. I really just want all combinations up to a certain length. So I decided to first get the ones that have exactly a particular length:
membersWithLength(Members, List, Bound) :-
L = Bound,
length(Members, L), members(Members, List).
This works great, e.g. for length 2:
[a,a]
[a,b]
[a,c]
...
And so on. Now my attempt to use clpfd to leverage the above function to get all lists up to a certain length went awry:
:- use_module(library(clpfd)).
membersLessThan(Members, List, Bound) :-
L in 0..Bound, % I also tried L #=< Bound
membersWithLength(Members, List, L).
Kind of works. Finds the right results (lists with length less than Bound).
But after it finds them, it loops continuously searching for more results. E.g. for length 2:
[]
[a]
[b]
[c]
[a,a]
[a,b]
...
[c,c]
Hangs looking for more solutions.
I guess this is the heart of my question. Can someone explain why (according to the trace) prolog continues to check larger and larger lists as possible solutions, even though they are all doomed to failure? And can someone tell me if there's a way to help prolog avoid this doomed journey?
I ultimately used the following code to solve the problem, but I was disappointed that I couldn't figure out how to use clpfd's integer constraints to constrain the size of the lists.
membersLessThan_(Members, List, Bound) :-
numlist(0,Bound,ZeroToBound),
member(L, ZeroToBound),
membersWithLength(Members, List, L).
Here is all the relevant code on SWISH: http://swish.swi-prolog.org/p/allcombos.pl

With you original implementation of members, if you want to enumerate all the answers you can do:
length(L, _), members(L, [a,b,c]).
which gives you the answers:
L = [] ;
L = [a] ;
L = [b] ;
L = [c] ;
L = [a, a] ;
L = [a, b] ;
L = [a, c] ;
L = [b, a] ;
L = [b, b] ;
L = [b, c] ;
L = [c, a] ;
L = [c, b] ;
L = [c, c] ;
L = [a, a, a] ;
L = [a, a, b] ;
L = [a, a, c] ;
L = [a, b, a]
This is a common idiom for iterative deepening, which allows you to list all the answers fairly. I don't think clpfd can help you in this case.
EDIT
I see that in the title you explicitly ask about CLPFD. The reason your code doesn't work is that when you do
L in 0..Bound
you are not actually enumerating those values. For the next predicates, L is still unbound and carries a constraint. So membersWithLength will keep looping trying new lengths, and once the length it's instantiated, it will see that the constraint fails and try again. You can see it in these examples:
L in 0..2, length(X, L)
loops like in your code, because length keeps trying. If you want to limit it, L has to be instantiated before calling length. You can use label for that. This next example doesn't loop:
L in 0..2, label([L]), length(X, L)

Related

Equality of sets

Can anyone help me with the following task: I need to define a predicate eq_set, which succeeds if the sets S1 and S2 are equal when it comes to the number of their elements.
But it works only if they are exactly the same number and order. I want to create a code that shows all varieties and doesn't take order into account. Can you help me,please?
I wrote:
eq_set([],[]).
eq_set([H|T],[H|T1]) :-
eq_set(T,T1).
But it works only if they are exactly the same number and order. I want to create a code that shows all varieties and doesn't take order into account.
The closest translation I have of the assignment, which is in Bulgarian, is: "Define the predicate eq_set, which succeeds if the sets (S1, S2) coincide.
You call them "sets" but the data structure you are using is a list. It is easiest to just sort the two lists:
eq_set(A, B) :-
% prerequisites: A and B are lists without duplicates
sort(A, S),
sort(B, S).
If you want something more complicated (for some reason) you need to be more specific.
With this definition:
?- eq_set([a,b,c], [a,b]).
false. % OK
?- eq_set([a,b,c], [a,b,c]).
true. % OK
?- eq_set([a,c,b], [a,b,c]).
true. % OK
?- eq_set([a,a,b], [a,b,b]).
true. % Not sure....
It really really depends on how the predicate is going to be used.
Assuming that a "set" is indeed a Prolog list without duplicates but not in any particular order; then two sets in that presentation "coincide" if they are permutations of each other. In other words, it would be enough to define eq_set/2 as:
eq_set(A, B) :-
my_permutation(A, B).
and just use the textbook definition of permutation/2 which uses the textbook definition of select/3 (See "The Art of Prolog (Second Edition)" by Sterling and Shapiro, pp 67-9):
my_permutation([], []).
my_permutation(Xs, [Y|Ys]) :-
my_select(Y, Xs, Xs0),
my_permutation(Xs0, Ys).
my_select(X, [X|Xs], Xs).
my_select(X, [Y|Ys], [Y|Zs]) :-
my_select(X, Ys, Zs).
(I renamed those just to make sure I am not using the standard library definitions; SWI-Prolog has both select/3 and permutation/2 in the autoloaded library(lists); the definitions are basically the same, but they do some run-time type-checking on the arguments.)
Here is how you can use it:
?- eq_set([1,2,3], [2,3,1]).
true ;
false.
?- eq_set([1,2,3], S).
S = [1, 2, 3] ;
S = [1, 3, 2] ;
S = [2, 1, 3] ;
S = [2, 3, 1] ;
S = [3, 1, 2] ;
S = [3, 2, 1] ;
false.
?- eq_set([1,2,3], [1,2]).
false.
?- eq_set(A, B).
A = B, B = [] ;
A = B, B = [_4480] ;
A = B, B = [_4480, _4492] ;
...
I am not sure how useful the last query is. You can force it to enumerate solutions in order of increasing size of the "set", like this:
?- length(S1, _), eq_set(S1, S2), numbervars(S1).
S1 = S2, S2 = [] ;
S1 = S2, S2 = [A] ;
S1 = S2, S2 = [A, B] ;
S1 = [A, B],
S2 = [B, A] ;
S1 = S2, S2 = [A, B, C] ;
S1 = [A, B, C],
S2 = [A, C, B] ;
S1 = [A, B, C],
S2 = [B, A, C] ;
S1 = [A, B, C],
S2 = [B, C, A] ;
S1 = [A, B, C],
S2 = [C, A, B] ;
S1 = [A, B, C],
S2 = [C, B, A] ;
S1 = S2, S2 = [A, B, C, D] .
(Don't worry about the numbervars, it is just there to give readable names to all the free variables in the sets. Keep in mind that unifying two free variables makes them the same variable.)
This is a starting point, but maybe it is already good enough. The most glaring omission is that it doesn't require the arguments to be lists without duplicates. One way to define this would be to require that each element is different from all other elements. Since "is different" is commutative, you can define it like this:
is_set([]).
is_set([X|Xs]) :-
all_different(Xs, X),
is_set(Xs).
all_different([], _).
all_different([Y|Ys], X) :-
dif(X, Y),
all_different(Ys, X).
This uses dif/2 which is a widely available predicate (but does your Prolog have it?).
We would have maybe used maplist for that last one:
is_set([]).
is_set([X|Xs]) :-
maplist(dif(X), Xs).
is_set(Xs).
You are pretty close in your solution.
We have two cases
1) The first list argument is bigger
2) The second list argument is bigger
If you already know which one is bigger, you can just do
%in case the left one is longer
eq_set_left(_,[]).
eq_set_left(X,[H|T]):-member(H,X), eq_set_left(X,T).
So a very simple solution and yet very optimal could be this:
%in case the right one is longer
eq_set_right([],_).
eq_set_right([H|T], X):- member(H,X), eq_set_right(T,X).
%in case the left one is longer
eq_set_left(_,[]).
eq_set_left(X,[H|T]):-member(H,X), eq_set_left(X,T).
%both cases, equal length is also included here
eq_set(X,Y):- eq_set_left(X,Y).
eq_set(X,Y):- eq_set_right(X,Y).
eq_set(X, Y) is true if either X is subset of Y, Y is subset of X or they are equal
A set is defined as a collection of distinct things where order is not important, which is to say that sets {a,b,c} and {b,a,c} are identical.
From that, one could say that two sets are identical if neither set contains an element that is not also found in the other (or conversely, two sets are not identical if either set contains an element not found in the other.
From that, one could simply say:
eq_set(Xs,Ys) :-
findall( (Xs,Ys) , ( member(X,Xs), \+ member(X,Ys) ), [] ),
findall( (Xs,Ys) , ( member(Y,Ys), \+ member(Y,Xs) ), [] )
.
Or if you don't want to use the built-in findall/3,
eq_set(Xs,Ys) :-
a_not_in_b( Xs , Ys , [] ) ,
a_not_in_b( Ys , Xs , [] ) .
a_not_in_b( [] , [] , [] ) .
a_not_in_b( [A|As] , Bs , Xs ) :- member(A,Bs) , a_not_in_b( As, Bs, Xs ) .
a_not_in_b( [A|As] , Bs , Xs ) :- a_not_in_b( As, Bs, [A|Xs] ) .
One should note that both of these has roughly O(N2) performance. If the sets in question are large, you might want to first sort each set and then merge the two sorted lists to identify those elements that are not common to both sets:
eq_set(Xs,Ys) :-
sort(Xs,X1),
sort(Ys,Y1),
X1 == Y1.

Prolog Out of stack error

I'm working on Problem 26 from 99 Prolog Problems:
P26 (**) Generate the combinations of K distinct objects chosen from
the N elements of a list
Example:
?- combination(3,[a,b,c,d,e,f],L).
L = [a,b,c] ;
L = [a,b,d] ;
L = [a,b,e] ;
So my program is:
:- use_module(library(clpfd)).
combination(0, _, []).
combination(Tot, List, [H|T]) :-
length(List, Length), Tot in 1..Length,
append(Prefix, [H], Stem),
append(Stem, Suffix, List),
append(Prefix, Suffix, SubList),
SubTot #= Tot-1,
combination(SubTot, SubList, T).
My query result starts fine but then returns a Global out of stack error:
?- combination(3,[a,b,c,d,e,f],L).
L = [a, b, c] ;
L = [a, b, d] ;
L = [a, b, e] ;
L = [a, b, f] ;
Out of global stack
I can't understand why it works at first, but then hangs until it gives Out of global stack error. Happens on both SWISH and swi-prolog in the terminal.
if you try to input, at the console prompt, this line of your code, and ask for backtracking:
?- append(Prefix, [H], Stem).
Prefix = [],
Stem = [H] ;
Prefix = [_6442],
Stem = [_6442, H] ;
Prefix = [_6442, _6454],
Stem = [_6442, _6454, H] ;
...
maybe you have a clue about the (main) problem. All 3 vars are free, then Prolog keeps on generating longer and longer lists on backtracking. As Boris already suggested, you should keep your program far simpler... for instance
combination(0, _, []).
combination(Tot, List, [H|T]) :-
Tot #> 0,
select(H, List, SubList),
SubTot #= Tot-1,
combination(SubTot, SubList, T).
that yields
?- aggregate(count,L^combination(3,[a,b,c,d,e],L),N).
N = 60.
IMHO, library(clpfd) isn't going to make your life simpler while you're moving your first steps into Prolog. Modelling and debugging plain Prolog is already difficult with the basic constructs available, and CLP(FD) is an advanced feature...
I can't understand why it works at first, but then hangs until it gives Out of global stack error.
The answers Prolog produces for a specific query are shown incrementally. That is, the actual answers are produced lazily on demand. First, there were some answers you expected, then a loop was encountered. To be sure that a query terminates completely you have to go through all of them, hitting SPACE/or ; all the time. But there is a simpler way:
Simply add false at the end of your query. Now, all the answers are suppressed:
?- combination(3,[a,b,c,d,e,f],L), false.
ERROR: Out of global stack
By adding further false goals into your program, you can localize the actual culprit. See below all my attempts: I started with the first attempt, and then added further false until I found a terminating fragment (failure-slice).
combination(0, _, []) :- false. % 1st
combination(Tot, List, [H|T]) :-
length(List, Length), Tot in 1..Length, % 4th terminating
append(Prefix, [H], Stem), false, % 3rd loops
append(Stem, Suffix, List), false, % 2nd loops
append(Prefix, Suffix, SubList),
SubTot #= Tot-1, false, % 1st loops
combination(SubTot, SubList, T).
To remove the problem with non-termination you have to modify something in the remaining visible part. Evidently, both Prefix and Stem occur here for the first time.
The use of library(clpfd) in this case is very suspicious. After length(List, Length), Length is definitely bound to a non-negative integer, so why the constraint? And your Tot in 1..Length is weird, too, since you keep on making a new constrained variable in every step of the recursion, and you try to unify it with 0. I am not sure I understand your logic overall :-(
If I understand what the exercise is asking for, I would suggest the following somewhat simpler approach. First, make sure your K is not larger than the total number of elements. Then, just pick one element at a time until you have enough. It could go something like this:
k_comb(K, L, C) :-
length(L, N),
length(C, K),
K =< N,
k_comb_1(C, L).
k_comb_1([], _).
k_comb_1([X|Xs], L) :-
select(X, L, L0),
k_comb_1(Xs, L0).
The important message here is that it is the list itself that defines the recursion, and you really don't need a counter, let alone one with constraints on it.
select/3 is a textbook predicate, I guess you should find it in standard libraries too; anyway, see here for an implementation.
This does the following:
?- k_comb(2, [a,b,c], C).
C = [a, b] ;
C = [a, c] ;
C = [b, a] ;
C = [b, c] ;
C = [c, a] ;
C = [c, b] ;
false.
And with your example:
?- k_comb(3, [a,b,c,d,e,f], C).
C = [a, b, c] ;
C = [a, b, d] ;
C = [a, b, e] ;
C = [a, b, f] ;
C = [a, c, b] ;
C = [a, c, d] ;
C = [a, c, e] ;
C = [a, c, f] ;
C = [a, d, b] ;
C = [a, d, c] ;
C = [a, d, e] ;
C = [a, d, f] ;
C = [a, e, b] ;
C = [a, e, c] . % and so on
Note that this does not check that the elements of the list in the second argument are indeed unique; it just takes elements from distinct positions.
This solution still has problems with termination but I don't know if this is relevant for you.

Coroutining in Prolog: when argument is a list (it has fixed length)

Question
Is it possible to schedule a goal to be executed as soon as the length of a list is known / fixed or, as #false pointed out in the comments, a given argument becomes a [proper] list? Something along this line:
when(fixed_length(L), ... some goal ...).
When-conditions can be constructed using ?=/2, nonvar/1, ground/1, ,/2, and ;/2 only and it seems they are not very useful when looking at the whole list.
As a further detail, I'm looking for a solution that presents logical-purity if that is possible.
Motivation
I think this condition might be useful when one wants to use a predicate p(L) to check a property for a list L, but without using it in a generative way.
E.g. it might be the case that [for efficiency or termination reasons] one prefers to execute the following conjunction p1(L), p2(L) in this order if L has a fixed length (i.e. L is a list), and in reversed order p2(L), p1(L) otherwise (if L is a partial list).
This might be achieved like this:
when(fixed_length(L), p1(L)), p2(L).
Update
I did implement a solution, but it lacks purity.
It would be nice if when/2 would support a condition list/1. In the meantime, consider:
list_ltruth(L, Bool) :-
freeze(L, nvlist_ltruth(L, Bool)).
nvlist_ltruth(Xs0, Bool) :-
( Xs0 == [] -> Bool = true
; Xs0 = [_|Xs1] -> freeze(Xs1, nvist_ltruth(Xs1, Bool))
; Bool = false
).
when_list(L, Goal_0) :-
nvlist_ltruth(L, Bool),
when(nonvar(Bool),( Bool == true, Goal_0 )).
So you can combine this also with other conditions.
Maybe produce a type error, if L is not a list.
when(nonvar(Bool), ( Bool == true -> Goal_0 ; sort([], L) ).
Above trick will only work in an ISO conforming Prolog system like SICStus or GNU that produces a type_error(list,[a|nonlist]) for sort([],[a|nonlist]), otherwise replace it by:
when(nonvar(Bool),
( Bool == true -> Goal_0 ; throw(error(type_error(list,L), _)).
Many systems contain some implementation specific built-in like '$skip_list' to traverse lists rapidly, you might want to use it here.
I've managed to answer my own question, but not with a pure solution.
Some observations
The difficulty encountered in writing a program that schedules some goal for execution when the length of a list is precisely known is the fact that the actual condition might change. Consider this:
when(fixed_length(L), Goal)
The length of the list might change if L is unbound or if the last tail is unbound. Say we have this argument L = [_,_|Tail]. L has a fixed width only if Tail has a fixed width (in other words, L is a list if T is a list). So, a condition that checks Tail might be the only thing to do at first. But if Tail becomes [a|Tail2] a new when-condition that tests if Tail2 is a list is needed.
The solution
1. Getting the when-condition
I've implemented a predicate that relates a partial list with the when-condition that signals when it might become a list (i.e. nonvar(T) where T is the deepest tail).
condition_fixed_length(List, Cond):-
\+ (List = []),
\+ \+ (List = [_|_]),
List = [_|Tail],
condition_fixed_length(Tail, Cond).
condition_fixed_length(List, Cond):-
\+ \+ (List = []),
\+ \+ (List = [_|_]),
Cond = nonvar(List).
2. Recursively when-conditioning
check_on_fixed_length(List, Goal):-
(
condition_fixed_length(List, Condition)
->
when(Condition, check_on_fixed_length(List, Goal))
;
call(Goal)
).
Example queries
Suppose we want to check that all elements of L are a when the size of L is fixed:
?- check_on_fixed_length(L, maplist(=(a), L)).
when(nonvar(L), check_on_fixed_length(L, maplist(=(a), L))).
... and then L = [_,_|Tail]:
?- check_on_fixed_length(L, maplist(=(a), L)), L = [_,_|L1].
L = [_G2887, _G2890|L1],
when(nonvar(L1), check_on_fixed_length([_G2887, _G2890|L1], maplist(=(a), [_G2887, _G2890|L1]))).
?- check_on_fixed_length(L, maplist(=(a), L)), L = [_,_|L1], length(L1, 3).
L = [a, a, a, a, a],
L1 = [a, a, a].
Impurity
conditon_fixed_length/2 is the source of impurity as it can be seen from the following query:
?- L = [X, Y|Tail], condition_fixed_length(L, Cond), L = [a,a].
L = [a, a],
X = Y, Y = a,
Tail = [],
Cond = nonvar([]).
?- L = [X, Y|Tail], L = [a, a], condition_fixed_length(L, Cond).
false.

Count occurrences Prolog

I'm new in Prolog and trying to do some programming with Lists
I want to do this :
?- count_occurrences([a,b,c,a,b,c,d], X).
X = [[d, 1], [c, 2], [b, 2], [a, 2]].
and this is my code I know it's not complete but I'm trying:
count_occurrences([],[]).
count_occurrences([X|Y],A):-
occurrences([X|Y],X,N).
occurrences([],_,0).
occurrences([X|Y],X,N):- occurrences(Y,X,W), N is W + 1.
occurrences([X|Y],Z,N):- occurrences(Y,Z,N), X\=Z.
My code is wrong so i need some hits or help plz..
Here's my solution using bagof/3 and findall/3:
count_occurrences(List, Occ):-
findall([X,L], (bagof(true,member(X,List),Xs), length(Xs,L)), Occ).
An example
?- count_occurrences([a,b,c,b,e,d,a,b,a], Occ).
Occ = [[a, 3], [b, 3], [c, 1], [d, 1], [e, 1]].
How it works
bagof(true,member(X,List),Xs) is satisfied for each distinct element of the list X with Xs being a list with its length equal to the number of occurrences of X in List:
?- bagof(true,member(X,[a,b,c,b,e,d,a,b,a]),Xs).
X = a,
Xs = [true, true, true] ;
X = b,
Xs = [true, true, true] ;
X = c,
Xs = [true] ;
X = d,
Xs = [true] ;
X = e,
Xs = [true].
The outer findall/3 collects element X and the length of the associated list Xs in a list that represents the solution.
Edit I: the original answer was improved thanks to suggestions from CapelliC and Boris.
Edit II: setof/3 can be used instead of findall/3 if there are free variables in the given list. The problem with setof/3 is that for an empty list it will fail, hence a special clause must be introduced.
count_occurrences([],[]).
count_occurrences(List, Occ):-
setof([X,L], Xs^(bagof(a,member(X,List),Xs), length(Xs,L)), Occ).
Note that so far all proposals have difficulties with lists that contain also variables. Think of the case:
?- count_occurrences([a,X], D).
There should be two different answers.
X = a, D = [a-2]
; dif(X, a), D = [a-1,X-1].
The first answer means: the list [a,a] contains a twice, and thus D = [a-2]. The second answer covers all terms X that are different to a, for those, we have one occurrence of a and one occurrence of that other term. Note that this second answer includes an infinity of possible solutions including X = b or X = c or whatever else you wish.
And if an implementation is unable to produce these answers, an instantiation error should protect the programmer from further damage. Something along:
count_occurrences(Xs, D) :-
( ground(Xs) -> true ; throw(error(instantiation_error,_)) ),
... .
Ideally, a Prolog predicate is defined as a pure relation, like this one. But often, pure definitions are quite inefficient.
Here is a version that is pure and efficient. Efficient in the sense that it does not leave open any unnecessary choice points. I took #dasblinkenlight's definition as source of inspiration.
Ideally, such definitions use some form of if-then-else. However, the traditional (;)/2 written
( If_0 -> Then_0 ; Else_0 )
is an inherently non-monotonic construct. I will use a monotonic counterpart
if_( If_1, Then_0, Else_0)
instead. The major difference is the condition. The traditional control constructs relies upon the success or failure of If_0 which destroys all purity. If you write ( X = Y -> Then_0 ; Else_0 ) the variables X and Y are unified and at that very point in time the final decision is made whether to go for Then_0 or Else_0. What, if the variables are not sufficiently instantiated? Well, then we have bad luck and get some random result by insisting on Then_0 only.
Contrast this to if_( If_1, Then_0, Else_0). Here, the first argument must be some goal that will describe in its last argument whether Then_0 or Else_0 is the case. And should the goal be undecided, it can opt for both.
count_occurrences(Xs, D) :-
foldl(el_dict, Xs, [], D).
el_dict(K, [], [K-1]).
el_dict(K, [KV0|KVs0], [KV|KVs]) :-
KV0 = K0-V0,
if_( K = K0,
( KV = K-V1, V1 is V0+1, KVs0 = KVs ),
( KV = KV0, el_dict(K, KVs0, KVs ) ) ).
=(X, Y, R) :-
equal_truth(X, Y, R).
This definition requires the following auxiliary definitions:
if_/3, equal_truth/3, foldl/4.
If you use SWI-Prolog, you can do :
:- use_module(library(lambda)).
count_occurrences(L, R) :-
foldl(\X^Y^Z^(member([X,N], Y)
-> N1 is N+1,
select([X,N], Y, [X,N1], Z)
; Z = [[X,1] | Y]),
L, [], R).
One thing that should make solving the problem easier would be to design a helper predicate to increment the count.
Imagine a predicate that takes a list of pairs [SomeAtom,Count] and an atom whose count needs to be incremented, and produces a list that has the incremented count, or [SomeAtom,1] for the first occurrence of the atom. This predicate is easy to design:
increment([], E, [[E,1]]).
increment([[H,C]|T], H, [[H,CplusOne]|T]) :-
CplusOne is C + 1.
increment([[H,C]|T], E, [[H,C]|R]) :-
H \= E,
increment(T, E, R).
The first clause serves as the base case, when we add the first occurrence. The second clause serves as another base case when the head element matches the desired element. The last case is the recursive call for the situation when the head element does not match the desired element.
With this predicate in hand, writing count_occ becomes really easy:
count_occ([], []).
count_occ([H|T], R) :-
count_occ(T, Temp),
increment(Temp, H, R).
This is Prolog's run-of-the-mill recursive predicate, with a trivial base clause and a recursive call that processes the tail, and then uses increment to account for the head element of the list.
Demo.
You have gotten answers. Prolog is a language which often offers multiple "correct" ways to approach a problem. It is not clear from your answer if you insist on any sort of order in your answers. So, ignoring order, one way to do it would be:
Sort the list using a stable sort (one that does not drop duplicates)
Apply a run-length encoding on the sorted list
The main virtue of this approach is that it deconstructs your problem to two well-defined (and solved) sub-problems.
The first is easy: msort(List, Sorted)
The second one is a bit more involved, but still straight forward if you want the predicate to only work one way, that is, List --> Encoding. One possibility (quite explicit):
list_to_rle([], []).
list_to_rle([X|Xs], RLE) :-
list_to_rle_1(Xs, [[X, 1]], RLE).
list_to_rle_1([], RLE, RLE).
list_to_rle_1([X|Xs], [[Y, N]|Rest], RLE) :-
( dif(X, Y)
-> list_to_rle_1(Xs, [[X, 1],[Y, N]|Rest], RLE)
; succ(N, N1),
list_to_rle_1(Xs, [[X, N1]|Rest], RLE)
).
So now, from the top level:
?- msort([a,b,c,a,b,c,d], Sorted), list_to_rle(Sorted, RLE).
Sorted = [a, a, b, b, c, c, d],
RLE = [[d, 1], [c, 2], [b, 2], [a, 2]].
On a side note, it is almost always better to prefer "pairs", as in X-N, instead of lists with two elements exactly, as in [X, N]. Furthermore, you should keep the original order of the elements in the list, if you want to be correct. From this answer:
rle([], []).
rle([First|Rest],Encoded):-
rle_1(Rest, First, 1, Encoded).
rle_1([], Last, N, [Last-N]).
rle_1([H|T], Prev, N, Encoded) :-
( dif(H, Prev)
-> Encoded = [Prev-N|Rest],
rle_1(T, H, 1, Rest)
; succ(N, N1),
rle_1(T, H, N1, Encoded)
).
Why is it better?
we got rid of 4 pairs of unnecessary brackets in the code
we got rid of clutter in the reported solution
we got rid of a whole lot of unnecessary nested terms: compare .(a, .(1, [])) to -(a, 1)
we made the intention of the program clearer to the reader (this is the conventional way to represent pairs in Prolog)
From the top level:
?- msort([a,b,c,a,b,c,d], Sorted), rle(Sorted, RLE).
Sorted = [a, a, b, b, c, c, d],
RLE = [a-2, b-2, c-2, d-1].
The presented run-length encoder is very explicit in its definition, which has of course its pros and cons. See this answer for a much more succinct way of doing it.
refining joel76 answer:
count_occurrences(L, R) :-
foldl(\X^Y^Z^(select([X,N], Y, [X,N1], Z)
-> N1 is N+1
; Z = [[X,1] | Y]),
L, [], R).

Finding all unifications in prolog

I wrote my first simple code in PROLOG:
is_beginning([], _).
is_beginning([FirstLetterB|RestWordB], [FirstLetterW|RestWordW]) :-
FirstLetterB == FirstLetterW,
is_beginning(RestWordB, RestWordW).
It is designed to find out if first argument of is_beginning is equal to the second one beginning.
Well, IMHO it can answer questions quite well, but now i wonder if there is any possibility of getting all possible answers for defined second argument.
eg. for
is_beginning(Answers, [a,b,c]);
i wish to get
[], [a], [a,b], [a,b,c]
as Answers unification, but I am getting only [] (simplest answer).
Is there any possibility of getting what I want? Maybe there is something wrong in my definition?
I already tried to use findall and forall, but it doesn't work to well for me :(
Thanks for all answers.
you are using (==)/2 when non needed (note the comment at end of documentation page). Indeed, if you change it to 'simple' unification (=)/2 your program works as you expect:
is_beginning([], _).
is_beginning([FirstLetterB|RestWordB], [FirstLetterW|RestWordW]) :-
FirstLetterB = FirstLetterW,
is_beginning(RestWordB, RestWordW).
test:
?- is_beginning(Answers, [a,b,c]).
Answers = [] ;
Answers = [a] ;
Answers = [a, b] ;
Answers = [a, b, c] ;
false.
The interpreter won't immediately return all solutions. When it returns [], press ";" to tell it to continue searching:
?- is_beginning(X, [a,b,c]).
X = [] ;
X = [a] ;
X = [a, b] ;
X = [a, b, c] ;
false.
If you need all these solutions in a Prolog list, rather than just printed out in the console, findall/3 is indeed what you're looking for:
?- findall(X, is_beginning(X, [a,b,c]), L).
L = [[], [a], [a, b], [a, b, c]].

Resources