I would like to get the middle element of a list in Prolog.
The predicates middle([1,2,3],M) and middle([1,2,3,4],M) should both return 2 as a result.
And I am allowed to use the predicate deleteLast.
I know that there are similar posts that solve that question but I have not found one that just uses deleteLast.
Even the syntax is not correct - however this is my solution so far:
middle([], _).
middle([X|XTail|Y], E) :-
1 is mod(list_length([X|XTail|Y], 2)),
middle([XTail], E).
middle([X|XTail|Y], E) :-
0 is mod(list_length([X|XTail|Y], 2)),
middle([X|XTail], E).
middle([X], X).
Question: Is that partly correct or am I completely on the wrong path ?
Sorry, the attempted solution you have is completely on the wrong path.
It doesn't use deleteLast/2 as you stated you require
You are using list_length/2 as if it were an arithmetic function, which it is not. It's a predicate.
You have a term with invalid syntax and unknown semantics, [X|XTail|Y]
In Prolog, you just need to think about it in terms of the rules. Here's an approach using deleteLast/2:
middle([X], X). % `X` is the middle of the single element list `[X]`
middle([X,_], X). % `X` is the middle of the two-element list `[X,_]`
% X is the middle of the list `[H|T]` if X is the middle of the list TWithoutLast
% where TWithoutLast is T with its last element removed
%
middle([H|T], X) :-
deleteLast(T, TWithoutLast),
middle(TWithoutLast, X).
I assume deleteLast/2 is well-behaved and just fails if T is empty.
You can also do this with same_length/2 and append/3, but, alas, doesn't use deleteLast/2:
middle(L, M) :-
same_length(L1, L2),
append(L1, [M|L2], L).
middle(L, M) :-
same_length(L1, L2),
append(L1, [M,_|L2], L).
So much unnecessary work, and unnecessary code. length/2 is very efficient, and a true relation. Its second argument is guaranteed to be a non-negative integer. So:
middle(List, Middle) :-
List = [_|_], % at least one element
length(List, Len),
divmod(Len, 2, Q, R), % if not available do in two separate steps
N is Q + R,
nth1(N, List, Middle).
And you are about ready:
?- middle(L, M), numbervars(L).
L = [A],
M = A ;
L = [A, B],
M = A ;
L = [A, B, C],
M = B ;
L = [A, B, C, D],
M = B ;
L = [A, B, C, D, E],
M = C ;
L = [A, B, C, D, E, F],
M = C .
I understand that this doesn't solve your problem (the answer by #lurker does) but it answers your question. :-(
Here is my attempt:
middle(L,M):- append(L1,L2,L),length(L1,N),length(L2,N), reverse(L1,[M|_]).
middle(L,M):- append(L1,L2,L),length(L1,N),length(L2,N1), N is N1+1 ,
reverse(L1,[M|_]).
Example:
?- middle([1,2,3],M).
M = 2 ;
false.
?- middle([1,2,3,4],M).
M = 2 ;
false.
In your implementation the problem is that by writing for example:
list_length([X|XTail|Y], 2)
The above does not give you as X the first element and as Y the last so I think it has some major problems...
As well pointed out by lurker you could write the above solution in one clause without using reverse/2:
middle(L, M) :- append(L1, [M|T], L), length(L1, N), length([M|T], N1),
(N1 is N + 1 ; N1 is N + 2).
Also to make the solution more relational (also see mat's comment below) you could use CLPFD library and replace is/2 with #= like:
middle(L, M) :- append(L1, [M|T], L), length(L1, N), length([M|T], N1),
(N1 #= N + 1 ; N1 #= N + 2).
Another interesting solution is to consider this predicate for splitting a list in half:
half(List, Left, Right) :-
half(List, List, Left, Right).
half(L, [], [], L).
half(L, [_], [], L).
half([H|T], [_,_|T2], [H|Left], Right) :-
half(T, T2, Left, Right).
This predicate divides an even list into two equal halves, or an odd list into two pieces where the right half has one more element than the left. It does so by reducing the original list, via the second argument, by two elements, each recursive call, while at the same time reducing the original list by one element each recursive call via the first argument. When it recurses down to the second argument being zero or one elements in length, then the first argument represents the half that's left, which is the right-hand list.
Example results for half/3 are:
| ?- half([a,b,c], L, R).
L = [a]
R = [b,c] ? a
(1 ms) no
| ?- half([a,b,c,d], L, R).
L = [a,b]
R = [c,d] ? a
no
| ?-
We can't quite use this to easily find the middle element because, in the even case, we want the last element of the left hand list. If we could bias the right-hand list by an extra element, we could then pick off the head of the right-hand half as the "middle" element. We can accomplish this using the deleteLast/2 here:
middle([X], X).
middle(List, Middle) :-
deleteLast(List, ListWithoutLast),
half(ListWithoutLast, _, [Middle|_]).
The head of the right half list of the original list, with the last element deleted, is the "middle" element. We can also simply half/3 and combine it with middle/2 since we don't really need everything half/3 does (e.g., we don't need the left-hand list, or the tail of the right hand list):
middle([X], X).
middle(List, Middle) :-
deleteLast(List, ListWithoutLast),
middle(ListWithoutLast, ListWithoutLast, Middle).
middle([M|_], [], M).
middle([M|_], [_], M).
middle([_|T], [_,_|T2], Right) :-
middle(T, T2, Right).
Another approach would be to modify half/3 to bias the splitting of the original list in half toward the right-hand half, which eliminates the need for using deleteLast/2.
modified_half(List, Left, Right) :-
modified_half(List, List, Left, Right).
modified_half(L, [_], [], L).
modified_half(L, [_,_], [], L).
modified_half([H|T], [_,_,X|T2], [H|Left], Right) :-
modified_half(T, [X|T2], Left, Right).
This will bias the right hand list to have an extra element at the "expense" of the left:
| ?- modified_half([a,b,c,d,e], L, R).
L = [a,b]
R = [c,d,e] ? a
no
| ?- modified_half([a,b,c,d,e,f], L, R).
L = [a,b]
R = [c,d,e,f] ? a
no
| ?-
Now we can see that the middle element, per the original definition, is just the head of the right hand list. We can create a new definition for middle/2 using the above. As we did before with half/3, we can ignore everything but the head in the right half, and we can eliminate the left half since we don't need it, and create a consolidated middle/2 predicate:
middle(List, Middle) :-
middle(List, List, Middle).
middle([M|_], [_,_], M).
middle([M|_], [_], M).
middle([_|T], [_,_,X|T2], Middle) :-
middle(T, [X|T2], Middle).
This reduces the original list down one element at a time (first argument) and two elements at a time (second argument) until the second argument is reduced to one or two elements. It then considers the head first argument to be the middle element:
This gives:
| ?- middle([a,b,c], M).
M = b ? ;
no
| ?- middle([a,b,c,d], M).
M = b ? ;
no
| ?- middle(L, M).
L = [M,_] ? ;
L = [M] ? ;
L = [_,M,_,_] ? ;
L = [_,M,_] ? ;
L = [_,_,M,_,_,_] ? ;
L = [_,_,M,_,_] ? ;
L = [_,_,_,M,_,_,_,_] ?
...
Related
So I'm making a predicate called removeN(List1, N, List2). It should basically function like this:
removeN([o, o, o, o], 3, List2).
List2 = [o].
The first argument is a list with a number of the same members ([o, o, o] or [x, x, x]). The second argument is the number of members you wanna remove, and the third argument is the list with the removed members.
How should I go about this, I was thinking about using length of some sort.
Thanks in advance.
Another approach would be to use append/3 and length/2:
remove_n(List, N, ShorterList) :-
length(Prefix, N),
append(Prefix, ShorterList, List).
Think about what the predicate should describe. It's a relation between a list, a number and a list that is either equal to the first or is missing the specified number of the first elements. Let's pick a descriptive name for it, say list_n_removed/3. Since you want a number of identical elements to be removed, let's keep the head of the list for comparison reasons, so list_n_removed/3 is just the calling predicate and another predicate with and additional argument, let's call it list_n_removed_head/4, describes the actual relation:
list_n_removed([X|Xs],N,R) :-
list_n_removed_head([X|Xs],N,R,X).
The predicate list_n_removed_head/4 has to deal with two distinct cases: either N=0, then the first and the third argument are the same list or N>0, then the head of the first list has to be equal to the reference element (4th argument) and the relation has to hold for the tail as well:
list_n_removed_head(L,0,L,_X).
list_n_removed_head([X|Xs],N,R,X) :-
N>0,
N0 is N-1,
list_n_removed_head(Xs,N0,R,X).
Now let's see how it works. Your example query yields the desired result:
?- list_n_removed([o,o,o,o],3,R).
R = [o] ;
false.
If the first three elements are not equal the predicate fails:
?- list_n_removed([o,b,o,o],3,R).
false.
If the length of the list equals N the result is the empty list:
?- list_n_removed([o,o,o],3,R).
R = [].
If the length of the list is smaller than N the predicate fails:
?- list_n_removed([o,o],3,R).
false.
If N=0 the two lists are identical:
?- list_n_removed([o,o,o,o],0,R).
R = [o, o, o, o] ;
false.
If N<0 the predicate fails:
?- list_n_removed([o,o,o,o],-1,R).
false.
The predicate can be used in the other direction as well:
?- list_n_removed(L,0,[o]).
L = [o] ;
false.
?- list_n_removed(L,3,[o]).
L = [_G275, _G275, _G275, o] ;
false.
However, if the second argument is variable:
?- list_n_removed([o,o,o,o],N,[o]).
ERROR: >/2: Arguments are not sufficiently instantiated
This can be avoided by using CLP(FD). Consider the following changes:
:- use_module(library(clpfd)). % <- new
list_n_removed([X|Xs],N,R) :-
list_n_removed_head([X|Xs],N,R,X).
list_n_removed_head(L,0,L,_X).
list_n_removed_head([X|Xs],N,R,X) :-
N #> 0, % <- change
N0 #= N-1, % <- change
list_n_removed_head(Xs,N0,R,X).
Now the above query delivers the expected result:
?- list_n_removed([o,o,o,o],N,[o]).
N = 3 ;
false.
As does the most general query:
?- list_n_removed(L,N,R).
L = R, R = [_G653|_G654],
N = 0 ;
L = [_G653|R],
N = 1 ;
L = [_G26, _G26|R],
N = 2 ;
L = [_G26, _G26, _G26|R],
N = 3 ;
.
.
.
The other queries above yield the same answers with the CLP(FD) version.
Alternative solution using foldl/4:
remove_step(N, _Item, Idx:Tail, IdxPlusOne:Tail) :-
Idx < N, succ(Idx, IdxPlusOne).
remove_step(N, Item, Idx:Tail, IdxPlusOne:NewTail) :-
Idx >= N, succ(Idx, IdxPlusOne),
Tail = [Item|NewTail].
remove_n(List1, N, List2) :-
foldl(remove_step(N), List1, 0:List2, _:[]).
The idea here is to go through the list while tracking index of current element. While element index is below specified number N we essentially do nothing. After index becomes equal to N, we start building output list by appending all remaining elements from source list.
Not effective, but you still might be interested in the solution, as it demonstrates usage of a very powerful foldl predicate, which can be used to solve wide range of list processing problems.
Counting down should work fine
removeN([],K,[]) :- K>=0.
removeN(X,0,X).
removeN([_|R],K,Y) :- K2 is K-1, removeN(R,K2,Y).
This works for me.
I think this is the easiest way to do this.
trim(L,N,L2). L is the list and N is number of elements.
trim(_,0,[]).
trim([H|T],N,[H|T1]):-N1 is N-1,trim(T,N1,T1).
I am trying to make use of prolog predicates and find middle element of a given list. My idea was to cut first and last element of list using recursion.Unfortunately I dont know how to handle recursion call properly.
delete_last(L, L1) :-
append(L1, [_], L).
delete_first(L,L1) :-
append([_],L1,L).
check_len(L) :-
length(L,LEN), \+ 1 is LEN.
delete_both([],_):-
false.
delete_both([_,_],_) :-
false.
delete_both([X],X):-
true, write('MidElement').
delete_both(L,L2) :-
delete_first(LT,L2), delete_last(L,LT),check_len(LT)
->write('here should be recursive call only when length is more than one').
I would be grateful for any help.
It would save a lot of typing if you checked the length of the list, calculated the position of the middle element, and only then traversed the list to get the element at that position. With SWI-Prolog, this would be:
?- length(List, Len),
divmod(Len, 2, N, 1),
nth0(N, List, a).
List = [a], Len = 1, N = 0 ;
List = [_G2371, a, _G2377], Len = 3, N = 1 ;
List = [_G2371, _G2374, a, _G2380, _G2383], Len = 5, N = 2 . % and so on
This solution makes sure the list has an odd length. You can see the documentation of divmod/4 if you need to define it yourself. Or, if the list does not have to have and odd, length, just use N is Len div 2. If for some reason you are not allowed to use nth0/3, it is still an easier predicate to implement than what you are trying to do.
You can tighten up what you have quite a bit as follows:
delete_last(L, L1) :-
append(L1, [_], L).
delete_first([_|L], L).
% No need to check length of 1, since we only need to check
% if L = [X] in the caller, so we'll eliminate this predicate
%check_len(L) :-
% length(L, 1). % No need for an extra variable to check length is 1
% Clauses that yield false are not needed since clauses already fail if not true
% So you can just remove those
%
delete_both([X], X) :-
write('MidElement').
% Here you need to fix the logic in your main clause
% You are deleting the first element of the list, then the last element
% from that result and checking if the length is 1.
delete_both(L, X) :-
delete_first(L, L1), % Remove first and last elements from L
delete_last(L1, LT),
( LT = [X] % Check for length of 1
-> true
; delete_both(LT, X) % otherwise, X is result of delete_both(LT, X)
).
With results:
| ?- delete_both([a,b,c,d,e], X).
X = c
yes
| ?- delete_both([a,b,c,d,e,f], X).
no
A DCG solution also works well here:
% X is the middle if it is flanked by two sequences of the same length
%
middle(X) --> seq(N), [X], seq(N).
seq(0) --> [].
seq(N) --> [_], { N #= N1 + 1 }, seq(N1).
middle(List, X) :- phrase(middle(X), List).
With results:
| ?- middle([a,b,c,d,e], X).
X = c ? ;
(1 ms) no
| ?- middle(L, a).
L = [a] ? ;
L = [_,a,_] ? ;
L = [_,_,a,_,_] ?
...
Another possible solution is to use SWI Prolog's append/2 predicate, which appends a list of lists (assuming you're using SWI):
middle(L, X) :-
same_length(Left, Right),
append([Left, [X], Right], L).
same_length([], []).
same_length([_|T1], [_|T2]) :- same_length(T1, T2).
In all of the above solutions, the predicate fails if the list has an even number of elements. Since that's what your original solution does, I assumed that's what is required. If there is a specific requirement for even lists, that needs to be stated clearly.
As a Prolog newbie, I try to define a predicate filter_min/2 which takes two lists to determine if the second list is the same as the first, but with all occurrences of the minimum number removed.
Sample queries with expected results:
?- filter_min([3,2,7,8], N).
N = [3,7,8].
?- filter_min([3,2,7,8], [3,7,8]).
true.
I tried but I always get the same result: false. I don't know what the problem is. I need help!
Here is my code:
filter_min(X,Y) :-
X == [],
write("ERROR: List parameter is empty!"),
!;
min_list(X,Z),
filter(X,Y,Z).
filter([],[],0).
filter([H1|T1],[H2|T2],Z) :-
\+ number(H1),
write("ERROR: List parameter contains a non-number element"),
!;
H1 \= Z -> H2 is H1, filter(T1,T2,Z);
filter(T1,T2,Z).
There are a couple of problems with your code:
filter([],[],0). will not unify when working with any list that does not have 0 as its minimum value, which is not what you want. You want it to unify regardless of the minimum value to end your recursion.
The way you wrote filter([H1|T1],[H2|T2],Z) and its body will make it so that the two lists always have the same number of elements, when in fact the second one should have at least one less.
A correct implementation of filter/3 would be the following:
filter([],[],_).
filter([H1|T1],L2,Z):-
\+ number(H1),
write("ERROR: List parameter contains a non-number element"),
!;
H1 \= Z -> filter(T1,T2,Z), L2 = [H1|T2];
filter(T1,L2,Z).
A bounty was offered...
... for a pure solution that terminates for (certain) cases where neither the length of the first nor of the second argument is known.
Here's a candidate implementation handling integer values, built on clpfd:
:- use_module(library(clpfd)).
filter_min(Xs,Ys) :-
filter_min_picked_gt(Xs,_,false,Ys).
filter_min_picked_gt([] ,_,true ,[]).
filter_min_picked_gt([Z|Xs],M,Picked,[Z|Zs]) :-
Z #> M,
filter_min_picked_gt(Xs,M,Picked,Zs).
filter_min_picked_gt([M|Xs],M,_,Zs) :-
filter_min_picked_gt(Xs,M,true,Zs).
Some sample queries:
?- filter_min([3,2,7,8],[3,7,8]).
true ; false. % correct, but leaves choicepoint
?- filter_min([3,2,7,8],Zs).
Zs = [3,7,8] ; false. % correct, but leaves choicepoint
Now, some queries terminate even though both list lengths are unknown:
?- filter_min([2,1|_],[1|_]).
false. % terminates
?- filter_min([1,2|_],[3,2|_]).
false. % terminates
Note that the implementation doesn't always finitely fail (terminate) in cases that are logically false:
?- filter_min([1,2|_],[2,1|_]). % does _not_ terminate
For a Prolog newbie, better start with the basics. The following works when first argument is fully instantiated, and the second is an uninstantiated variable, computing the result in one pass over the input list.
% remmin( +From, -Result).
% remmin([],[]). % no min elem to remove from empty list
remmin([A|B], R):-
remmin(B, A, [A], [], R). % remove A from B to get R, keeping [A]
% in case a smaller elem will be found
remmin([C|B], A, Rev, Rem, R):-
C > A -> remmin(B, A, [C|Rev], [C|Rem], R) ;
C==A -> remmin(B, A, [C|Rev], Rem, R) ;
C < A -> remmin(B, C, [C|Rev], Rev, R).
remmin([], _, _, Rem, R) :- reverse(Rem, R).
First, we can get the minimum number using the predicate list_minnum/2:
?- list_minnum([3,2,7,8],M).
M = 2.
We can define list_minnum/2 like this:
list_minnum([E|Es],M) :-
V is E,
list_minnum0_minnum(Es,V,M).
list_minnum0_minnum([],M,M).
list_minnum0_minnum([E|Es],M0,M) :-
M1 is min(E,M0),
list_minnum0_minnum(Es,M1,M).
For the sake of completeness, here's the super-similar list_maxnum/2:
list_maxnum([E|Es],M) :-
V is E,
list_maxnum0_maxnum(Es,V,M).
list_maxnum0_maxnum([],M,M).
list_maxnum0_maxnum([E|Es],M0,M) :-
M1 is max(E,M0),
list_maxnum0_maxnum(Es,M1,M).
Next, we use meta-predicate tfilter/3 in tandem with dif/3 to exclude all occurrences of M:
?- M=2, tfilter(dif(M),[2,3,2,7,2,8,2],Xs).
Xs = [3,7,8].
Put the two steps together and define min_excluded/2:
min_excluded(Xs,Ys) :-
list_minnum(Xs,M),
tfilter(dif(M),Xs,Ys).
Let's run some queries!
?- min_excluded([3,2,7,8],Xs).
Xs = [3,7,8].
?- min_excluded([3,2,7,8,2],Xs).
Xs = [3,7,8].
I am given 2 lists for example K=[a,b,c,d,e,f,g] and L=[a,b,1,d,e,2,g]. When these 2 lists have 2 different elements, then they are friendly.
This is what I've tried:
friendly(K,L):-
append(L1,[Z],A1),
append(A1,L2,A2),
append(A2,[Q],A3),
append(A3,L3,K),
append(L1,[Y],B1),
append(B1,L2,B2),
append(B2,[W],B3),
append(B3,L3,L),
Z\=Y,
Q\=W.
Thank you all so much, at last I found the correct code:
friend(L1,L2):-
append(A,Y,L1),
append([Z|T],[F|TT],Y),
append(A,Q,L2),
append([R|T],[O|TT],Q),
Z\=R,
F\=O.
You can use append/3 in this way to locate the first different elements.
first_different(L1,L2, R1,R2) :-
append(H, [E1|R1], L1),
append(H, [E2|R2], L2),
E1 \= E2.
H is the common part, R1,R2 are the 'remainders'. This code is more in line with your second comment above.
Now you must apply two times this helper predicate, and the second time also 'remainders' must be equal, or one of them must be empty. That is
friendly(L1,L2) :-
first_different(L1,L2,R1,R2),
first_different(R1,R2,T1,T2),
once((T1=T2;T1=[];T2=[])).
Alternatively, using some builtin can be rewarding. This should work
friendly(L1,L2) :- findall(_,(nth1(I,L1,E1),nth1(I,L2,E2),E1\=E2),[_,_]).
Wouldn't it be better to do something like the following?
diff([], [], []).
diff([], K, K).
diff(L, [], L).
diff([H | TL], [H | TK], D) :- diff(TL, TK, D),!.
diff([HL | TL], [HK | TK], [HL, HK | D]) :- diff(TL, TK, D),!.
friendly(K, L) :- diff(K, L, D), length(D, Length), Length < 3.
But your problem really is underspecified. For example my program really cares about order so [a,x,b] and [a,b] are not friendly by my definition.
I'm still a little uncertain about the total definition of "friendly" list, but I think this might answer it:
friendly(A, B) :-
friendly(A, B, 2).
friendly([H|TA], [H|TB], C) :-
C > 0,
friendly(TA, TB, C).
friendly([HA|TA], [HB|TB], C) :-
HA \= HB,
C > 0,
C1 is C-1,
friendly(TA, TB, C1).
friendly(A, [], C) :-
length(A, L),
L =< C.
friendly([], B, C) :-
length(B, L),
L =< C.
friendly(A, A, 0).
I'm assuming that the definition of friendly means the lists are in "lock step" outside of the maximum of two differences.
Does order matter? Are the lists sets (each element is unique) or bags (duplicates allowed)?
Assuming that
Order doesn't matter ([1,2,3] and [1,3,2]) are treated as identical), and
Duplicates don't matter ([1,2,3,1] and [1,2,3]) are treated as identical
Something like this might be along the lines of what you're looking for:
friendly(Xs,Ys) :-
set_of(
E ,
(
( member(E,Xs) ,
not( member(E,Ys) )
)
;
(
member(E,Ys) ,
not( member(E,Xs) )
) ,
Zs
) ,
length( Zs , L ) ,
L =< 2
.
Find the set of all elements of each list that aren't in the other and succeed if the resulting list is of length 0, 1 or 2.
I came up with something similar to others.. I just keep a list of '_' items (final param of diff_list) - one for each difference, be that a value difference at the same index, or a difference in the length, then finally in friendly/2, check that has 2 items.
% recursion base
diff_list([], [], []).
% the head of both lists are the same, don't add to diff list
diff_list([HK|TK], [HK|TL], Diff) :-
diff_list(TK, TL, Diff).
% the above rule failed, so must be a difference, add a '_'
diff_list([_|TK], [_|TL], [_|Diff]) :-
diff_list(TK, TL, Diff).
% 1st list is empty, but the 2nd isn't. That's a diff again.
diff_list([], [_|TL], [_|Diff]) :-
diff_list([], TL, Diff).
% 2nd list is empty, but the 1st isn't. Another diff.
diff_list([_|TK], [], [_|Diff]) :-
diff_list(TK, [], Diff).
% friendly is true if the diff list length unifies with 2 item length list [_,_]
friendly(K, L) :-
diff_list(K, L, [_,_]).
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".
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).
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)
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)).
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.
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).
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.