Why are so many correct solutions found? - prolog

Suppose I have a list of "base atoms" and a longer atom made up only of those base atoms. repeats are allowed. I whipped up the following code to generate lists of all the atoms which could possibly make up the longer atom. This code seems to work with the exception that it finds many repeats of the same (correct) solutions and I am not sure why?
basics([a, abc, def, aaa]).
candidate(aaaabcaaadef).
join_atoms(Atoms, Atom):- join_atoms( Atoms, '', Atom ) .
join_atoms( [], Atom, Atom ) .
join_atoms( [H|T], AtomAccum, Atom ) :-
atom_concat( AtomAccum, H, UpdatedAtom) ,
join_atoms( T, UpdatedAtom, Atom ) .
split_atoms( C, Atoms ):- split_atoms( C, [], Atoms ) .
split_atoms( '', AtomsAccum, Atoms ) :-
candidate(C) ,
reverse( AtomsAccum, AtomsAccumR ) ,
join_atoms( AtomsAccumR, C ) ,
Atoms = AtomsAccumR .
split_atoms(C, AtomsAccum, Atoms):-
basics( B ) ,
member( SubAtom, B ) ,
sub_atom( C, _, Length, _, SubAtom ) ,
sub_atom( C, Length, _, 0, AtomRest ) ,
split_atoms(AtomRest, [SubAtom|AtomsAccum], Atoms).
main:-
candidate( C ) ,
findall( Atoms, split_atoms(C, Atoms), AllAtoms ) ,
sort( AllAtoms, UniqueAtoms ) ,
write(UniqueAtoms),
nl .
The findall/3 and sort/2 will get all solutions and remove the duplicates, of course. But without those the correct solutions are repeated multiple times.
For example (output truncated)
| ?- split_atoms(aaaabcaaadef, Atoms).
Atoms = [a,a,a,abc,a,a,a,def] ? a
Atoms = [a,a,a,abc,a,a,a,def]
Atoms = [a,a,a,abc,a,a,a,def]
Atoms = [a,a,a,abc,a,a,a,def]
Atoms = [a,a,a,abc,a,a,a,def]
Atoms = [a,a,a,abc,a,a,a,def]
Atoms = [a,a,a,abc,aaa,def]
Atoms = [a,a,a,abc,a,a,a,def]
Atoms = [a,a,a,abc,a,a,a,def]
.
.
.
Can anyone suggest why this is happening? Presumably it is backtracking more than necessary for some reason? Or perhaps my code is unintentionally creating a situation which can be minimized?

I think you are over-thinking the problem here.
To paraphrase your problem statement:
I want find all the different, distinct ways a given symbol can be composed from an alphabet of shorter symbols.
To solve that requires a couple of observations:
The longer symbol must have as a prefix one of the shorter symbols contained in the alphabet
The above recursively holds true if you strip such a prefix off the longer symbol
That leads to this simple solution: https://swish.swi-prolog.org/p/tLTQiVNQ.pl
[sub_atom/5 is an ISO-standard built-in predicate that lets you disassemble atoms by offset and length]
% --------------------------------------
% compose( Atom, Subatoms, Composition )
% --------------------------------------
compose( '' , _ , [] ) . % the empty set composes the empty atom
compose( Atom , Subatoms , [A|As] ) :- % otherwise...
member(A,Subatoms) , % - fish a symbol out of our alphabet
sub_atom(Atom,0,L,P,A) , % - see if its a prefix of our candidate
sub_atom(Atom,L,P,_,Nextatom) , % - get the next atom (the suffix)
compose(Nextatom, Subatoms,As) % - and recurse down
. % Easy!
Given your sample data:
?- compose( aaaabcaaadef, [a,abc,def,aaa], Xs).
The following results are produced on backtracking:
Xs = [a, a, a, abc, a, a, a, def]
Xs = [a, a, a, abc, aaa, def]
Xs = [aaa, abc, a, a, a, def]
Xs = [aaa, abc, aaa, def]
false

Why are so many correct solutions found?
Not so fast! Let's start with a related question:
Why are so many incorrect solutions almost found?
To answer that question, let me modify your program by negating one single goal:
split_atoms( '', AtomsAccum, Atoms ) :-
candidate(C) ,
reverse( AtomsAccum, AtomsAccumR ) ,
\+ join_atoms( AtomsAccumR, C ) , % <=== negated
Atoms = AtomsAccumR .
split_atoms(C, AtomsAccum, Atoms):-
basics( B ) ,
member( SubAtom, B ) ,
sub_atom( C, _, Length, _, SubAtom ) ,
sub_atom( C, Length, _, 0, AtomRest ) ,
split_atoms(AtomRest, [SubAtom|AtomsAccum], Atoms).
?- split_atoms(aaaabcaaadef, Atoms).
Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,def,def]
; Atoms = [a,a,a,a,a,a,aaa,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,a,a,a,def]
; Atoms = [a,a,a,a,a,a,def,def]
; ... .
So now, we are looking at near-solutions that your program will have to consider and only filter out in the very last moment. That does not look very right, does it? So your program considers much too many candidates only to weed them out anyway.
What you need is some specialization of your program. Often (as in this case) it suffices to add some further goals:
... .
split_atoms(C, AtomsAccum, Atoms):-
basics( B ) ,
member( SubAtom, B ) ,
Before = 0, % specialization
sub_atom( C, Before, Length, _, SubAtom ) ,
sub_atom( C, Length, _, 0, AtomRest ) ,
split_atoms(AtomRest, [SubAtom|AtomsAccum], Atoms).
And now, there are no longer any near-solutions.
Even better you can replace this by:
... .
split_atoms(C, AtomsAccum, Atoms):-
basics( B ) ,
member( SubAtom, B ) ,
atom_concat(SubAtom, AtomRest, C),
split_atoms(AtomRest, [SubAtom|AtomsAccum], Atoms).
And even more so, you can remove basics/1 and candidate/1 as has been suggested by #NicholasCarey.

An alternative solution using DCG:
split_atom(Atom, Atoms) :-
atom_chars(Atom, Chars),
phrase(list_of_atoms(Atoms), Chars).
list_of_atoms([A|As]) --> basic_atom(A), list_of_atoms(As).
list_of_atoms([]) --> \+ [_].
basic_atom(a) --> [a].
basic_atom(aaa) --> [a,a,a].
basic_atom(abc) --> [a,b,c].
basic_atom(def) --> [d,e,f].
Example:
?- time(forall(split_atom(aaaabcaaadef, Atoms), writeln(Atoms))).
[a,a,a,abc,a,a,a,def]
[a,a,a,abc,aaa,def]
[aaa,abc,a,a,a,def]
[aaa,abc,aaa,def]
% 60 inferences, 0.000 CPU in 0.016 seconds (0% CPU, Infinite Lips)
true.

Related

Removing duplicates from a list in prolog

I'm trying to implement a simple predicate, that would simply remove items that occur more than once in a list.
For instace, for,
unique([a,b,a,b,c,c,a], R)
should be R = [a,b,c]
unique([], []).
unique([X], [X]).
unique([H|T], [H|R]) :-
not_contains(H, R),
unique(T, R).
unique([H|T], R) :-
contains(H, R),
unique(T, R).
contains(_, []).
contains(X, [X|T]).
not_contains(_, []).
not_contains(X, [H|T]) :-
X \= H,
not_contains(X, T).
I am unsure what I'm doing wrong. If the item is not contained within R, add to it and repeat, and if is, don't add it and proceed with iteration.
A fun way to do it that I just thought of:
nub(L,R):- maplist( p(R), L), length(R,_), !.
p(R,E):- memberchk(E,R).
nub(L,R) makes a unique list R out of an input list L. It assumes R is a non-instantiated variable before the call is made, and L is a fully ground list.
This uses the result list as its own uniqueness accumulator while it is being built!
Testing:
6 ?- nub([a,b,a,b,c,c,a], R).
R = [a, b, c].
The easiest way to make a list unique is just use the built-in sort/2:
unique(Xs,Ys) :- sort(Xs,Ys).
so unique( [c,a,b,a] , Rs ) yields Rs = [a,b,c].
If you want to maintain order, you need to decide on the strategy you want to use — in case of duplicates, which duplicate "wins": First or last?
The "last wins" strategy is the simplest to implement:
unique( [] , [] ) . % the empty list is itself a unique set
unique( [X|Xs] , Ys ) :- % A non-empty list is unique if . . .
contains(X,Xs), % - X is contained within the source list's tail,
!, - and (eliminating the choice point)
unique( Xs, Ys ) . - omitting X, the remainder of the list is (recursively) unique
unique( [X|Xs] , Ys ) :- % Otherwise, the non-empty list is unique if . . .
unique( Xs,[X|Ys] ) . % - adding X to the results, the remainder of the list is (recursively) unique .
Here, unique( [a,b,a,c,a], Rs ) yields Rs = [b,c,a].
If you want to use the "first wins" strategy, you'll be wanting to use a helper predicate with an accumulator that grows the result list in reverse order, which is then reversed. That gives us something like this:
unique( Xs , Ys ) :- unique(Xs,[],Zs), reverse(Zs,Ys) .
unique( [] , Ys , Ys ) . % Source list exhausted? we're done.
unique( [X|Xs] , Ts , Ys ) :- % Otherwise . . .
contains(X,Ts) , % - if X is found in the accumulator,
!, % - eliminate the choice point, and
unique(Xs,Ts,Ys) . % - recurse down, discarding X
unique( [X|Xs] , Ts , Ys ) :- % Otherwise (X is unique) . . .
unique(Xs,[X|Ts],Ys) . % - recurse down, prepending X to the accumulator
And here, unique( [a,b,a,c,a], Rs ) yields Rs = [a,b,c].
You can avoid the use of reverse/2 here, by building the 2 lists (accumulator and final set) in parallel. A trade-off, though: memory for speed:
unique( Xs , Ys ) :- unique(Xs,[],Ys) .
unique( [] , _ , [] ) .
unique( [X|Xs] , Ts , Ys ) :- memberchk(X,Ts), !, unique( Xs, Ts , Ys ) .
unique( [X|Xs] , Ts , [X|Ys] ) :- unique( Xs, [X|Ts] , Ys ) .
You don't really need a contains/2 predicate: the in-built member/2 and memberchk/2 do exactly what you want. member/2 is non-deterministic and will succeed once for every time the item is found in the list; memberchk/2 is non-deterministic and will succeed at most once.
Since this is testing for uniqueness, memberchk/2 is what you'd want, giving you this:
contains(X,Ys) :- memberchk(X,Ys) .
Or you can roll you own (it's trivial):
contains( X , [X|Ys] ) :- ! .
contains( X , [_|Ys] ) :- contains(X,Ys) .
Or even simpler, just a one-liner:
contains( X , [Y|Ys] ) :- X = Y -> true ; contains(X,Ys) .

Prolog binary counter

i'm trying to do a program that counts the sequence of binary numbers, let me give an example
the input is [0,0,0,1,1,0,0,0,1,1,1,1]
The output should be [0(the first number),3(number of 0 in sequence),2 (number of 1 in sequence),3,4]
the input size is infinite and it needs to be a list, so far what I have done is this:
list([H|T],[X|Y]):-
T = [], X is H, Y is 1.
list([H|T],[X|Y]):-
T \= [], X is H,X1 is 1, contlist([H|T],[X1,Y]).
contlist([H|T],[X,_]):-
T \= [],
H =:= [T|_},
T1 i
contlist([H|T],[X,_]):-
X1 is X+1.
I don't know how to compare the head with the head of the tail and how to continue from there, maybe someone can help me?
This is a special case of Run-length encoding suitable for binary sequences.
You begin noting the first bit and start counting either 1s or 0s, when the bit flips you "output" the number and start counting the other bit value. Every time the sequence flips bits you output the number and start counting again until the whole sequence is processed. Note this procedure is not reversible. To make it reversible you would probably want to use clp(FD).
rle_binary([B|Seq], [B|BRLE]):-
binary(B),
rle_binary(Seq, B, 1, BRLE).
rle_binary([], _, N, [N]).
rle_binary([B|Seq], B, N, BRLE):-
succ(N, N1),
rle_binary(Seq, B, N1, BRLE).
rle_binary([B1|Seq], B, N, [N|BRLE1]):-
binary(B1),
B \= B1,
rle_binary(Seq, B1, 1, BRLE1).
binary(0).
binary(1).
Sample run:
?- rle_binary( [0,0,0,1,1,0,0,0,1,1,1,1], BRLE).
BRLE = [0, 3, 2, 3, 4] ;
false.
What you're talking about is Run-Length Encoding.
It's easy to implement. Executing the below code as
?- run_length_encoding( [a,b,b,c,c,c] , Rs ) .
Yields
Rs = [ a:1, b:2, c:3 ]
[The code doesn't care what the list contains (outside of perhaps unbound variables)]
You can fiddle with it at: https://swish.swi-prolog.org/p/PrtWEfZx.pl
run_length_encoding( Xs, Ys ) :- nonvar(Xs), ! , rle_encode(Xs,Ys) .
run_length_encoding( Xs, Ys ) :- nonvar(Ys), rle_decode(Ys,Xs) .
rle_encode( [] , [] ) .
rle_encode( [X|Xs] , Rs ) :- rle_encode(Xs,X:1,Rs) .
rle_encode( [X|Xs] , Y:N , [Y:N|Rs] ) :- X \= Y , ! , rle_encode(Xs,X:1,Rs) .
rle_encode( [X|Xs] , X:N , Rs ) :- M is N+1 , ! , rle_encode(Xs,X:M,Rs) .
rle_encode( [] , X:N , [X:N] ) .
rle_decode( [] , [] ) .
rle_decode( [X:N|Xs] , [X|Ys] ) :- N > 0, !, M is N-1, rle_decode([X:M|Xs],Ys) .
rle_decode( [_:0|Xs] , Ys ) :- rle_decode(Xs,Ys) .
Using SWI-Prolog predicates clumped/2 and pairs_values/2:
rle([X|Xs], [X|V]) :-
clumped([X|Xs], P),
pairs_values(P, V).
Example:
?- rle([0,0,0,1,1,0,0,0,1,1,1,1], L).
L = [0, 3, 2, 3, 4].

Definite Logic Program

The aim is to implement the predicate noDupl/2.
The first argument of this predicate is the list to analyze and second argument is the list of numbers which are no duplicate.
I could not understand code below and when I compiled it, it gave an error message that contained is undefined procedure, however as a hint it is written that we can use as predefined predicate contained and notContained. I think I need to define contained and notContained.
noDupl(XS, Res):-
help( XS, [],Res).
help([],_,[]).
help([X|XS],Seen,[X|Res]):-
notContained(X,XS),
notContained(X,Seen),
help(XS, [X|Seen], Res).
help([X|XS],Seen,Res):-
contained(X,Seen),
help(XS, Seen, Res).
help([X|XS],Seen,Res):-
contained(X,XS),
help(XS, [X|Seen], Res).
Could someone please explain me the problem.
The missing definitions might be:
contained(X,[X|_]).
contained(X,[E|Es]) :-
dif(X, E),
contained(X, Es).
notContained(_X, []).
notContained(X, [E|Es]) :-
dif(X, E),
notContained(X, Es).
(I like to call these relations rather memberd/2 and non_member/2.)
The definition you gave extends the relation with an extra argument for the elements considered so far.
To understand the meaning of each clause, read each right-to-left in the direction of the arrow (the :- is a 1970's ASCII-fication of ←). Let's take the first rule:
Provided, that X is not an element of XS, and
provided, that X is not an element of Seen, and
provided, that help(X, [X|Seen], Res) is true,
then also help([X|XS],Seen,[X|Res]) is true.
In other words, if X is neither in the list of visited elements Seen nor in the elements yet to be visited XS, then it does not possess a duplicate.
What is a bit difficult to understand is whether or not the clauses you gave are mutually exclusive - this is, strictly speaking, not your concern, as long as you are only interested in declarative properties, but it is a good idea to avoid such redundancies.
Here is a case, where such redundancy shows:
?- noDupl([a,a,a],U).
U = []
; U = []
; false.
Ideally, the system would give one determinate answer:
?- noDupl([a,a,a], U).
U = [].
Personally, I do not like a lot to split things into too many cases. Essentially, we could have two: it is a duplicate, and it is none.
It is possible to provide a definition that is correct and still fully determinate for the cases where determinism is possible - such as when the first argument is "sufficiently instantiated" (which includes a ground list). Let's see if there are some answers into that direction.
I've annotated your code for you:
noDupl( XS , Res ) :- % Res is the [unique] set of element from the bag XS
help( XS, [],Res) % if invoking the helper succeeds.
. %
help( [] , _ , [] ) . % the empty list is unique.
help( [X|XS] , Seen , [X|Res] ) :- % A non-empty list is unique, if...
notContained(X,XS), % - its head (X) is not contained in its tail (XS), and
notContained(X,Seen), % - X has not already been seen, and
help(XS, [X|Seen], Res). % - the remainder of the list is unique.
help( [X|XS] , Seen , Res ) :- % otherwise...
contained(X,Seen) , % - if X has been seen,
help(XS, Seen, Res). % - we discard it and recurse down on the tail.
help([X|XS],Seen,Res):- % otherwise...
contained(X,XS), % - if X is in the tail of the source list,
help(XS, [X|Seen], Res). % - we discard it (but add it to 'seen').
Your contained/2 and notContained/2` predicates might be defined as this:
contained( X , [X|_] ) :- ! .
contained( X , [Y|Ys] ) :- X \= Y , contained( X , Ys ) .
not_contained( _ , [] ) .
not_contained( X , [Y|Ys] ) :- X \= Y , not_contained(X,Ys) .
Now, I may be missing something in your code, but there's an awful lot of redundancy in it. You could simply write something like this (using the built-ins member/2 and reverse/2):
no_dupes( List , Unique ) :- no_dupes( Bag , [] , Set ) .
no_dupes( [] , V , S ) . % if we've exhausted the bag, the list of visited items is our set (in reverse order of the source)
reverse(V,S) % - reverset it
. % - to put our set in source order
no_dupes( [X|Xs] , V , S ) :- % otherwise ...
( member(X,V) -> % - if X is already in the set,
V1 = V % - then we discard X
; V1 = [X|V] % - else we add X to the set
) , % And...
no_dupes( Xs , V1 , S ) % we recurse down on the remainder
. % Easy!
Can this be done in a pure and efficient way?
Yes, by using
tpartition/4 and (=)/3 like so:
dups_gone([] ,[]).
dups_gone([X|Xs],Zs0) :-
tpartition(=(X),Xs,Ts,Fs),
if_(Ts=[], Zs0=[X|Zs], Zs0=Zs),
dups_gone(Fs,Zs).
Some sample ground queries (all of which succeed deterministically):
?- dups_gone([a,a,a],Xs).
Xs = [].
?- dups_gone([a,b,c],Xs).
Xs = [a, b, c].
?- dups_gone([a,b,c,b],Xs).
Xs = [a, c].
?- dups_gone([a,b,c,b,a],Xs).
Xs = [c].
?- dups_gone([a,b,c,b,a,a,a],Xs).
Xs = [c].
?- dups_gone([a,b,c,b,a,a,a,c],Xs).
Xs = [].
This also works with more general queries. Consider:
?- length(Xs,N), dups_gone(Xs,Zs).
N = 0, Xs = [], Zs = []
; N = 1, Xs = [_A], Zs = [_A]
; N = 2, Xs = [_A,_A], Zs = []
; N = 2, Xs = [_A,_B], Zs = [_A,_B], dif(_A,_B)
; N = 3, Xs = [_A,_A,_A], Zs = []
; N = 3, Xs = [_A,_A,_B], Zs = [_B], dif(_A,_B)
; N = 3, Xs = [_A,_B,_A], Zs = [_B], dif(_A,_B)
; N = 3, Xs = [_B,_A,_A], Zs = [_B], dif(_A,_B), dif(_A,_B)
; N = 3, Xs = [_A,_B,_C], Zs = [_A,_B,_C], dif(_A,_B), dif(_A,_C), dif(_B,_C)
; N = 4, Xs = [_A,_A,_A,_A], Zs = []
...

Writing a predicate for converting a float into a list of digits

I need to write a predicate that takes a float number and returns a list its digits. For example:
?- solA(0.1234, [], B).
B = [1,2,3,4]
This is my code:
addhead(X, L, [X|L]).
solA(0.0, _, _).
solA(A, B, H) :-
C is A*10,
D is float_integer_part(C),
E is round(D),
F is C-E,
addhead(E, B, G),
solA(F, G, H).
This is how I'd solve it:
digits_of( Number , Digits ) :-
number_codes( Number , Codes ) ,
findall( Digit , ( member(Code,Codes) , digit(Code,Digit) ) ,Digits )
.
digit(Code,Digit) :-
code_type(Code,digit) ,
Digit is Code - 48 , % 48 is code point for ASCII/Unicode zero ('0')
.
Because dealing with floating point jitter gives me a headache.

How do I make "intersection of 2 lists" predicate?

I'm trying to make intersection of 2 lists (i.e. list C contains those and only those elements, that are in A and B), yet as I understand, I get disjunction of 2 lists + any amount of any elements in C.
Intended to work like:
if X is in C, then it must be both in A and in B. (I believe X should iterate ALL members of C !?)
predicate: d(A,B,C) :- (member(X,D)->member(X,A),member(X,B)).
Can you tell: Are my sentence and predicate not equal or did I make another error?
example:
?- [user].
|: d(A,B,C) :- (member(X,D)->(member(X,A),member(X,B))).
|: % user://1 compiled 0.01 sec, 612 bytes
true.
?- d([a,b],[b,c],C)
| .
C = [b|_G21] .
?- d([a,b],[b,c],[b]).
true .
A O(NlogN) solution with duplicates removed:
% untested
intersection(A, B, O) :-
sort(A, AS),
sort(B, BS),
intersection1(AS, BS, O).
intersection1(A, B, O) :-
( A = [AH|AT],
B = [BH|BT]
-> ( AH == BH
-> O = [AH|OT],
intersection1(AT, BT, OT)
; ( AH #< BH
-> intersection1(AT, B, O)
; intersection1(A, BT, O) ) )
; O = [] ).
I like the solution proposed by #salva, though I'd do a more straightforward sort-and-merge, chucking anything that doesn't match instead:
intersect( As , Bs , Cs ) :-
sort( As , SortedAs ) ,
sort( Bs , SortedBs ) ,
merge( SortedAs , SortedBs , Cs )
.
merge( [] , [] , [] ).
merge( [] , [_|_] , [] ).
merge( [_|_] , [] , [] ).
merge( [C|As] , [C|Bs] , [C|Cs] ) :- merge( As , Bs , Cs ) .
merge( [A|As] , [B|Bs] , Cs ) :- A #< B , merge( As , [B|Bs] , Cs ) .
merge( [A|As] , [B|Bs] , Cs ) :- A #> B , merge( [A|As] , Bs , Cs ) .
your predicate d/3 should be reformulated in constructive terms, since Prolog it's 'a tuple at once' relational language:
d(X,Y,Z) :- findall(E, (member(E,X), memberchk(E,Y)), Z).
that yields
?- d([a,b],[b,c],C).
C = [b].
memberchk/2 it's the deterministic version of member/2, used here to enumerate all X' elements. You could understand better the difference if you replace memberchk with member and try to call d/3 with lists containing duplicates.
findall/3 it's the simpler 'all solutions' list constructor.

Resources