0
count([], 0, 0).
count([X|T], M, N) :- 1 is X, count(T, MRec, NRec), 
                              M is MRec, N is NRec+1.

count([X|T], M, N) :- 0 is X, count(T, MRec, NRec), 
                              M is MRec+1, N is NRec.

control_number(L) :- count_digit(L, M, N), 2 is M, 3 is N.


?- control_number([1,1,0,0,1]).
ERROR: count_number/3: Undefined procedure: count/3

Hello everybody, I need help. This code must provide the count of two separate number recursively. However, I cannot provide recursion with 2 parameters. I guess MRec and NRec is not valid in any way. Any help will be appreciated. Thanks now...

repeat
  • 18,496
  • 4
  • 54
  • 166

3 Answers3

3

Here is a more idiomatic rewrite:

count_digits([], 0, 0).
count_digits([1|T], M, N) :-
   count_digits(T, M, NRec),
   N is NRec+1.
count_digits([0|T], M, N) :-
   count_digits(T, MRec, N),
   M is MRec+1.

control_number(L) :-
   count_digits(L, 2, 3).

This can be improved a lot by using library(clpfd). Maybe someone else will answer.

false
  • 10,264
  • 13
  • 101
  • 209
3

As already pointed out by @false this predicate is quite a candidate for clpfd. Besides that I added constraints (marked as % <-) to ensure that M and N are greater than 0 in the recursive cases, so Prolog does not continue to search for further solutions once those variables have been reduced to 0.

:- use_module(library(clpfd)).

count_digits([], 0, 0).
count_digits([1|T], M, N) :-
   N #> 0,                        % <-
   NRec #= N-1,
   count_digits(T, M, NRec).
count_digits([0|T], M, N) :-
   M #> 0,                        % <-
   MRec #= M-1,
   count_digits(T, MRec, N).

With these minor modifications you can already use count_digits/3 in several ways. For example to ask for all lists with 2 0's and 3 1's:

   ?- count_digits(L,2,3).
L = [1,1,1,0,0] ? ;
L = [1,1,0,1,0] ? ;
L = [1,1,0,0,1] ? ;
L = [1,0,1,1,0] ? ;
L = [1,0,1,0,1] ? ;
L = [1,0,0,1,1] ? ;
L = [0,1,1,1,0] ? ;
L = [0,1,1,0,1] ? ;
L = [0,1,0,1,1] ? ;
L = [0,0,1,1,1] ? ;
no

Or count the occurrences of 0's and 1's in a given list:

   ?- count_digits([1,1,0,0,1],M,N).
M = 2,
N = 3
% 1

Or even ask for the number of 0's and 1's in a list containing variables:

   ?- count_digits([1,0,X,Y],M,N).
M = X = Y = 1,
N = 3 ? ;
M = N = 2,
X = 1,
Y = 0 ? ;
M = N = 2,
X = 0,
Y = 1 ? ;
M = 3,
N = 1,
X = Y = 0

This is quite nice already and one might be content with the predicate as is. It certainly is fine if you intend to use it with control_number/1 as suggested by @false. However it might be worth the time to fool around a little with some other queries. For example the most general query: What lists are there with M 0's and N 1's?

   ?- count_digits(L,M,N).
L = [],
M = N = 0 ? ;
L = [1],
M = 0,
N = 1 ? ;
L = [1,1],
M = 0,
N = 2 ? ;
L = [1,1,1],
M = 0,
N = 3 ?
...

It is only producing lists that consist of 1's exclusively. That is because the first recursive rule is the one describing the case with the 1 as the first element of the list. So the solutions are coming in an unfair order. What happens with the following query is maybe even somewhat less intuitive: What lists are there with the same (but not fixed) number of 0's and 1's:

   ?- count_digits(L,M,M).
L = [],
M = 0 ? ;

There is an answer and then the predicate loops. That's not exactly a desirable property. An interesting observation about this query: If one uses it on lists with fixed length the result is actually as expected:

   ?- length(L,_), count_digits(L,M,M).
L = [],
M = 0 ? ;
L = [1,0],
M = 1 ? ;
L = [0,1],
M = 1 ? ;
L = [1,1,0,0],
M = 2 ? ;
L = [1,0,1,0],
M = 2 ? ;
...

Applying this idea to the previous query yields a fair ordering of the results:

   ?- length(L,_), count_digits(L,M,N).
L = [],
M = N = 0 ? ;
L = [1],
M = 0,
N = 1 ? ;
L = [0],
M = 1,
N = 0 ? ;
L = [1,1],
M = 0,
N = 2 ? ;
L = [1,0],
M = N = 1 ? ;
...

It certainly would be nice to get these results without having to prefix an auxiliary goal. And looking a little closer at the relation described by count_digits/3 another observation meets the eye: If there are M 0's and N 1's the length of the list is actually fixed, namely to M+N. To put these observations to work one could rename count_digits/3 to list_0s_1s/3 and redefine count_digits/3 to be the calling predicate with the following constraints:

:- use_module(library(clpfd)).

count_digits(L,M,N) :-
   X #= M+N,
   length(L,X),               % L is of length M+N
   list_0s_1s(L,M,N).

list_0s_1s([], 0, 0).
list_0s_1s([1|T], M, N) :-
   N #> 0,
   NRec #= N-1,
   list_0s_1s(T, M, NRec).
list_0s_1s([0|T], M, N) :-
   M #> 0,
   MRec #= M-1,
   list_0s_1s(T, MRec, N).

The first three queries above yield the same results as before but these two are now producing results in a fair order without looping:

   ?- count_digits(L,M,N).
L = [],
M = N = 0 ? ;
L = [1],
M = 0,
N = 1 ? ;
L = [0],
M = 1,
N = 0 ? ;
L = [1,1],
M = 0,
N = 2 ? ;
L = [1,0],
M = N = 1 ? 
...

   ?- count_digits(L,M,M).
L = [],
M = 0 ? ;
L = [1,0],
M = 1 ? ;
L = [0,1],
M = 1 ? ;
L = [1,1,0,0],
M = 2 ? ;
L = [1,0,1,0],
M = 2 ? 
...

Two last notes on your predicate control_number/1: Firstly, if you are using is/2 make sure to use it like so:

   ?- M is 2.
M = 2
% 1

instead of (as used in your definition of control_number/1):

   ?- 2 is M.
     ERROR!!
     INSTANTIATION ERROR- in arithmetic: expected bound value
% 1

And secondly, if you intend to use a predicate like control_number/1 to call count_digits/3, don't put goals like M is 2 and N is 3 after the actual call of count_digits/3. That way you are asking for all solutions of count_digits(L,M,N), of which there are infinitely many, and in the subsequent goals you are then filtering out the ones that satisfy your constraints (M is 2 and N is 3). With this ordering of the goals you make sure that control_number/1 does not terminate after producing the finite number of solutions, since infinitely many solution-candidates are produced by the first goal that subsequently fail according to your constraints. Instead, place such constraints first or put them directly as arguments into the goal as posted by @false.

tas
  • 8,100
  • 3
  • 14
  • 22
  • 1
    @mat: Yes, it's amazing how a little parenthesis-shift can move an entire sentence towards the realm of grammatical correctness, isn't it? Thanks for the kudos :-D – tas Jun 06 '16 at 20:18
0

Accumulation parameters is the way to go (you need an auxiliary predicate in order to initialize those parameters):

count(List,C0,C1) :-
    count_aux(List,C0,C1,0,0).

count_aux([],C0,C1,C0,C1).
count_aux([0|Rest],C0,C1,PartialC0,PartialC1) :-
    IncC0 is PartialC0+1,
    !,
    count_aux(Rest,C0,C1,IncC0,PartialC1).
count_aux([1|Rest],C0,C1,PartialC0,PartialC1) :-
    IncC1 is PartialC1+1,
    !,
    count_aux(Rest,C0,C1,PartialC0,IncC1).
count_aux([_|Rest],C0,C1,PartialC0,PartialC1) :-
    count_aux(Rest,C0,C1,PartialC0,PartialC1).

Note:

  • You should call count/3, not count_aux/5.
  • Last two parameters to count_aux/5 are accumulation parameters initialized to zero.
  • First clause to count_aux/5 is the base case, where accumulated parameters are returned.
  • Last clause to count_aux/5 prevents predicate failure if list items are not 0 nor 1.

Example:

?- count([1,1,0,0,0,k],A,B).
A = 3,
B = 2.
Zebollo
  • 26
  • 1
  • *Quite* brittle! The code only works "as advertised" with sufficicnetThe goal `count([0,0,1],2,1)` succeeds (as expected), but the more general goal `count([_,_,_],2,1)` fails! – repeat Jun 08 '16 at 20:09