5

I wrote a Prolog program to find all solutions to any '8 out of 10 cats does countdown' number sequence. I am happy with the result. However, the solutions are not unique. I tried distincts() and reduced() from the "solution sequences" library. They did not produce unique solutions.

The problem is simple. you have a given list of six numbers [n1,n2,n3,n4,n5,n6] and a target number (R). Calculate R from any arbitrary combination of n1 to n6 using only +,-,*,/. You do not have to use all numbers but you can only use each number once. If two solutions are identical, only one must be generated and the other discarded. 

Sometimes there are equivalent results with different arrangement. Such as:

(100+3)*6*75/50+25
(100+3)*75*6/50+25  

Does anyone has any suggestions to eliminate such redundancy?

Each solution is a nested operators and integers. For example +(2,*(4,-(10,5))). This solution is an unbalanced binary tree with Arithmetic Operator for root and sibling nodes and numbers for leaf nodes. In order to have unique solutions, no two trees should be equivalent.

The Code:

:- use_module(library(lists)).
:- use_module(library(solution_sequences)).

solve(L,R,OP) :-
    findnsols(10,OP,solve_(L,R,OP),S),
    print_solutions(S).

solve_(L,R,OP) :-
    distinct(find_op(L,OP)),
    R =:= OP.

find_op(L,OP) :-
    select(N1,L,Ln),
    select(N2,Ln,[]),
    N1 > N2,
    member(OP,[+(N1,N2), -(N1,N2), *(N1,N2), /(N1,N2), N1, N2]).
find_op(L,OP) :-
    select(N,L,Ln),
    find_op(Ln,OP_),
    OP_ > N,
    member(OP,[+(OP_,N), -(OP_,N), *(OP_,N), /(OP_,N), OP_]).

print_solutions([]).
print_solutions([A|B]) :-
  format('~w~n',A),
  print_solutions(B).

Test:

solve([25,50,75,100,6,3],952,X)

Result

(100+3)*6*75/50+25 <- s1
((100+6)*3*75-50)/25 <- s2
(100+3)*75*6/50+25 <- s1
((100+6)*75*3-50)/25 <- s2
(100+3)*75/50*6+25 <- s1
true.

UPDATE: Generate solutions useing DCG

The following is an attempt to generate solutions using DCG.  I was able to generate a more exhaustive solution set than in previous code posted. In a way, using DCG resulted in a more correct and elegant code. However, it is much more difficult to 'guess' what the code is doing.

The issue of redundant solutions still persist.

:- use_module(library(lists)).
:- use_module(library(solution_sequences)).

s(L) --> [L].

s(+(L,Ls)) --> [L],s(Ls).
s(*(L,Ls)) --> [L],s(Ls), {L =\= 1, Ls =\= 1, Ls =\= 0}.

s(-(L,Ls)) --> [L],s(Ls), {L =\= Ls, Ls =\= 0}.
s(/(L,Ls)) --> [L],s(Ls), {Ls =\= 1, Ls =\= 0}.

s(-(Ls,L)) --> [L],s(Ls), {L =\= Ls}.
s(/(Ls,L)) --> [L],s(Ls), {L =\= 1, Ls =\=0}.

solution_list([N,H|[]],S) :-
    phrase(s(S),[N,H]).

solution_list([N,H|T],S) :-
    phrase(s(S),[N,H|T]);
    solution_list([H|T],S).

solve(L,R,S) :-
    permutation(L,X),
    solution_list(X,S),
    R =:= S.
Guy Coder
  • 24,501
  • 8
  • 71
  • 136
Mousali
  • 61
  • 1
  • 5
  • So, the idea is to "build a tree of arithmetic operations with the leafs from a known multiset of integers so that a certain value results". For french speakers who don't know BBC programming, this is [Le compte est bon](https://fr.wikipedia.org/wiki/Des_chiffres_et_des_lettres#Le_Compte_est_bon), although there the set is constrained to certain numbers. – David Tonhofer Jan 22 '20 at 10:13
  • 1
    This [Q&A](https://stackoverflow.com/q/42627198/1243762) should help bridge the gap from current programming to using DCGs. – Guy Coder Jan 23 '20 at 16:14
  • @GuyCoder: P.S. I do not ask for anyone to solve this problem for me. I only ask for hints. After all I am doing this as an exercise to get back into prolog after 20 from Uni days. Cheers, – Mousali Jan 25 '20 at 12:46
  • I am now going to clean up my comments that are not up-voted. Typically when one does this, the others do it as well to keep the list of comments small so that the comments are not automatically converted into a StackOverflow room. – Guy Coder Jan 25 '20 at 12:55
  • Of interest: [prolog dcg restriction](https://stackoverflow.com/q/14238644/1243762) – Guy Coder Jan 25 '20 at 13:08
  • 1
    Of interest: [Enumerate binary trees](https://codegolf.stackexchange.com/questions/112874/enumerate-binary-trees/112929#112929) – Guy Coder Jan 25 '20 at 13:11
  • Of interest: [Permuted combinations of the elements of a list - Prolog](https://stackoverflow.com/q/4578755/1243762) – Guy Coder Jan 25 '20 at 13:34
  • The desired symmetry-breaking (for addition and multiplication) is done in https://stackoverflow.com/a/74908845/ – brebs Feb 08 '23 at 21:49

2 Answers2

2

Does anyone has any suggestions to eliminate such redundancy?

I suggest to define a sorting weight on each node (inner or leaf). The number resulting from reducing the child node could be used, although ties will appear. These can be broken by additionally looking at topmost operations, sorting * before + for example. Actually one would like to have a sorting operation for which "tie" means "exactly the same subtree of arithmetic operations".

David Tonhofer
  • 14,559
  • 5
  • 55
  • 51
  • This is a good way. I have also thought of it.  But I am hoping there is a cleaner 'prolog' way that does not add additional complexity. – Mousali Jan 22 '20 at 11:20
  • @Mousali But problem does not have an in-built way to decide an task-specific equivalence relation on terms. I cannot decide that `1*2` is equivalent to `2*1` unless you help out. – David Tonhofer Jan 22 '20 at 11:30
  • @Mousali Wishing success! Post results! – David Tonhofer Jan 22 '20 at 11:47
  • I have a silly idea that might work. Compare the number of each operation type, the number of brackets, and the list of numbers.  If equal then solutions are probably equal. For exsample: [2,5,10,25] = [5,25,2,10] and [(,(,),),+,*,*] = [*,*,+,),),(,(]. – Mousali Jan 25 '20 at 01:30
2

Since the OP is only seeking hints to help solve the problem.

  1. Use DCG as a generator. (SWI-Prolog) (Prolog DCG Primer)
    a. For a more refined version of using DCGs as a generator look for examples that use length/2. When you understand why you might see a beam of light shining down on you for a few moments (The light beam is a video gaming thing).
  2. Use a constraint solver (SWI-Prolog) (CLP(FD) and CLP(ℤ): Prolog Integer Arithmetic) (Understanding CLP(FD) Prolog code of N-queens problem)
  3. Since your solutions are constrained to the 6 numbers and the operators are always binary operators (+,-,*,/) then it is possible to enumerate the unique binary trees. If you know about OEIS then you can find related links that can help you solve this problem, but you need to give OEIS a sequence. To get a sequence for use with OEIS draw the trees for N from 2 to 5 and then enter that sequence into OEIS and see what you get. e.g.
N is the number of leaf (*) nodes.

N=2  ( 1 way to draw the tree )
   -  
  / \  
 *   *  

N=3  ( 2 ways to draw the tree )
     -       -  
    / \     / \  
   -   *   *   -  
  / \         / \  
 *   *       *   *  

So the sequence starts with 1,2 ...

Hint - This page (link died) shows the images of the trees to see if you have done it correctly. In the description I use N to count the number of leaves (*), but on this page they use N to count the number of internal nodes (-). If we call my N N1 and the page N N2, then the relation is N2 = N1 - 1

  1. This might be a Hamiltonian Cycle (Wolfram World) (Hamiltonianicity of the Tower of Hanoi Problem) Remember that there is a relation between Binary Trees and the Tower of Hanoi, but in your case there are added constraints. I don't know if the constraints eliminate a solution as a Hamiltonian Cycle.

Also don't think of building the final answer from a combination of any number and operator, but instead build subsets of operators and numbers, and then use those subsets to build the answer. You constrain at the start, not at the end.

Or put another way, don't think combinations at the start, but permutations of combinations (not sure if that is the correct pattern, but in the ball park) and then using that build the tree.

Guy Coder
  • 24,501
  • 8
  • 71
  • 136
  • 1
    You are worth your weight in gold :). This is an excellent experience to get to know the power of prolog. I will keep working on it. – Mousali Jan 25 '20 at 13:55