1

I'm new to Prolog and I can't seem to get the answer to this on my own.

What I want is, that Prolog counts ever Number in a list, NOT every element. So for example:

getnumbers([1, 2, c, h, 4], X).

Should give me:

X=3

getnumbers([], 0).
getnumbers([_ | T], N) :- getnumbers(T, N1), N is N1+1.

Is what I've got, but it obviously gives me every element in a list. I don't know how and where to put a "only count numbers".

Majusbeh
  • 11
  • 1

6 Answers6

2

As usual, when you work with lists (and SWI-Prolog), you can use module lambda.pl found there : http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/lambda.pl

:- use_module(library(lambda)).

getnumbers(L, N) :-
    foldl(\X^Y^Z^(number(X)
             ->  Z is Y+1
             ;   Z = Y),
          L, 0, N).
joel76
  • 5,565
  • 1
  • 18
  • 22
1

Consider using the built-in predicates (for example in SWI-Prolog), and checking their implementations if you are interested in how to do it yourself:

include(number, List, Ns), length(Ns, N)

mat
  • 40,498
  • 3
  • 51
  • 78
  • Ah I see, that works amazingly well. Thanks, but can you maybe point me into the right direction, if I want to avoid using the built-in predicates? Like implement "only use numbers" into the existing code. From what I see it appears that you can use number/1 for example only while consulting prolog, is that true? – Majusbeh Apr 21 '13 at 16:49
1

Stay logically pure, it's easy: Use the meta-predicate tcount/3 in tandem with the reified type test predicate number_t/2 (short for number_truth/2):

number_t(X,Truth) :- number(X), !, Truth = true.
number_t(X,Truth) :- nonvar(X), !, Truth = false.
number_t(X,true)  :- freeze(X,  number(X)).
number_t(X,false) :- freeze(X,\+number(X)).

Let's run the query the OP suggested:

?- tcount(number_t,[1,2,c,h,4],N).
N = 3.                                       % succeeds deterministically

Note that this is monotone: delaying variable binding is always logically sound. Consider:

?- tcount(number_t,[A,B,C,D,E],N), A=1, B=2, C=c, D=h, E=4.
N = 3, A = 1, B = 2, C = c, D = h, E = 4 ;   % succeeds, but leaves choice point
false.

At last, let us peek at some of the answers of the following quite general query:

?- tcount(number_t,[A,B,C],N).
N = 3, freeze(A,  number(A)), freeze(B,  number(B)), freeze(C,  number(C)) ;
N = 2, freeze(A,  number(A)), freeze(B,  number(B)), freeze(C,\+number(C)) ;
N = 2, freeze(A,  number(A)), freeze(B,\+number(B)), freeze(C,  number(C)) ;
N = 1, freeze(A,  number(A)), freeze(B,\+number(B)), freeze(C,\+number(C)) ;
N = 2, freeze(A,\+number(A)), freeze(B,  number(B)), freeze(C,  number(C)) ;
N = 1, freeze(A,\+number(A)), freeze(B,  number(B)), freeze(C,\+number(C)) ;
N = 1, freeze(A,\+number(A)), freeze(B,\+number(B)), freeze(C,  number(C)) ;
N = 0, freeze(A,\+number(A)), freeze(B,\+number(B)), freeze(C,\+number(C)).
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
  • Ideally tests for `number/1`, `atom/1` are guarded by an explicit `nonvar/1` **as if** they would produce instantiation errors. – false Jun 16 '15 at 09:19
0

of course, you must check the type of an element to see if it satisfies the condition.

number/1 it's the predicate you're looking for.

See also if/then/else construct, to use in the recursive clause.

CapelliC
  • 59,646
  • 5
  • 47
  • 90
0

This uses Prolog's natural pattern matching with number/1, and an additional clause (3 below) to handle cases that are not numbers.

% 1 - base recursion
getnumbers([], 0).

% 2 - will pass ONLY if H is a number
getnumbers([H | T], N) :- 
    number(H),
    getnumbers(T, N1), 
    N is N1+1.

% 3 - if got here, H CANNOT be a number, ignore head, N is unchanged, recurse tail  
getnumbers([_ | T], N) :- 
    getnumbers(T, N).
magus
  • 1,347
  • 7
  • 13
  • The third clause also matches if head *is* a number. – mat Apr 22 '13 at 13:43
  • don't understand mat. if head is a number, it will be caught by the second rule, so the third rule is never reached, since the 3 clauses will be executed in order 1..2..3, or have i missed something ? – magus Apr 22 '13 at 17:01
  • If head is a number, both the second and third rule apply. Thanks to backtracking, both will be tried, and yes, in that order. Did you try the program for example on `?- getnumbers([1]).`? – mat Apr 23 '13 at 07:48
  • i understand that #2 and #3 *could* apply, but in reality the only circumstance where the 3rd rule could be selected by backtracking is if the 2nd one fails.. because number(H) fails. getnumbers([1]) looks ok.. 3rd clause is never used in the trace, correct result shown ? Re: the solution, are you saying that not(number(H)) should be the first line in #3 ? (Sorry.. i'm still not understanding your point - are you talking theoretically.. which clauses could be selected vs practically, which will be selected in this specific example) – magus Apr 24 '13 at 07:26
  • 1
    `?- getnumbers([1], N)` yields two solutions: The first solution is correct (`N=1`). On backtracking (in SWI-Prolog, press SPACE for additional solutions), the third clause is tried and applies, and you get an additional, *incorrect* solution (`N=0`). And yes, adding `\+ number(H)` (note that `(\+)/1` is ISO whereas `not/1` is not) to the third clause is one way to correct this. Another way to see this problem is to simply ask `?- getnumbers([1], 0).` and see that it succeeds. – mat Apr 24 '13 at 07:35
  • Excellent - many thanks for the clarifications and corrections. – magus Apr 24 '13 at 07:39
0

A common prolog idiom with this sort of problem is to first define your predicate for public consumption, and have it invoke a 'worker' predicate. Often it will use some sort of accumulator. For your problem, the public consumption predicate is something like:

count_numbers( Xs , N ) :-
  count_numbers_in_list( Xs , 0 , N ) .

count_numbers_in_list( [] , N , N ) .
count_numbers_in_list( [X|Xs] , T , N ) :-
  number(X) ,
  T1 is T+1 ,
  count_numbers_in_list( Xs , T1 , N )
  .

You'll want to structure the recursive bit so that it is tail recursive as well, meaning that the recursive call depends on nothing but data in the argument list. This allows the compiler to reuse the existing stack frame on each call, so the predicate becomes, in effect, iterative instead of recursive. A properly tail-recursive predicate can process a list of infinite length; one that is not will allocate a new stack frame on every recursion and eventually blow its stack. The above count_numbers_in_list/3 is tail recursive. This is not:

getnumbers([H | T], N) :- 
  number(H),
  getnumbers(T, N1), 
  N is N1+1.
Nicholas Carey
  • 71,308
  • 16
  • 93
  • 135