4
votes

I am aware on how to find the index of a specific element in Prolog but is there a way to find the index of the first instance of a number greater than say X. For instance, say I have a list of all ones but there is a random number greater than one somewhere in the list. How could I go about finding the index of the first instance of a number greater than 1? I am really new to Prolog and am not too good at subgoals of predicates.

4

4 Answers

5
votes

You want to write a relation between a list an index and a value. Let's call it list_1stindex_gt/3. It is opportune to have a fourth argument to keep track of the current index. However, it would be nice to not bother the user with this accumlator, so you could use and auxiliary predicate with an additional argument for the current index, let's call it list_1stindex_gt_/4. Assuming you want to start counting the indices at 1 (otherwise change the fourth argument to 0) you can define list_1stindex_gt/3 like so:

:-use_module(library(clpfd)).

list_1stindex_gt(L,I,GT) :-
   list_1stindex_gt_(L,I,GT,1).

For list_1stindex_gt_/4 you have 2 cases:

  1. The head of the list is greater than the third argument: Then you know the desired index.

  2. The head of the list is smaller or equal to the third argument: Then you increment the accumlator by 1 and continue the search in the tail of the list.

You can write that in Prolog like so:

list_1stindex_gt_([X|Xs],I,GT,I) :-       % case 1
   X #> GT.
list_1stindex_gt_([X|Xs],I,GT,Acc0) :-    % case 2
   X #=< GT,
   Acc1 #= Acc0+1,
   list_1stindex_gt_(Xs,I,GT,Acc1).

Example queries: At which index is the first element greater than 1 in the given list?

   ?- list_1stindex_gt([1,1,1,1,5,1,1,2],I,1).
I = 5 ? ;
no

At which index can the first element greater than 1 be in a list of three variables?

   ?- list_1stindex_gt([A,B,C],I,1).
I = 1,
A in 2..sup ? ;
I = 2,
A in inf..1,
B in 2..sup ? ;
I = 3,
A in inf..1,
B in inf..1,
C in 2..sup ? ;
no

At which index can the first element greater than the variable X be in a list of three variables?

   ?- list_1stindex_gt([A,B,C],I,X).
I = 1,
X#=<A+ -1 ? ;
I = 2,
X#>=A,
X#=<B+ -1 ? ;
I = 3,
X#>=A,
X#=<C+ -1,
X#>=B ? ;
no

Furthermore, you could consider @mat's suggested improvement from this answer to a previous question by you: Following the idea behind (#<)/3 you can define (#>)/3 and then define list_1stindex_gt_/4 using if_/3 like so:

:-use_module(library(clpfd)).

#>(X, Y, T) :-
        zcompare(C, X, Y),
        greater_true(C, T).

greater_true(<, false).
greater_true(>, true).
greater_true(=, false).

list_1stindex_gt(L,I,GT) :-
   list_1stindex_gt_(L,I,GT,1).

list_1stindex_gt_([X|Xs],I,GT,Acc0) :-
   if_(X #> GT,
       (I #= Acc0),
       (Acc1 #= Acc0+1, list_1stindex_gt_(Xs,I,GT,Acc1))).

This way the first query succeeds without leaving unnecessary choice points open:

?- list_1stindex_gt([1,1,1,1,5,1,1,2],I,1).
I = 5.
4
votes

Here's a slightly different take on it:

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

:- asserta(clpfd:full_answer).

zs_first_greater(Zs, Index, Pivot) :-
   append(Prefix, [E|_], Zs),
   maplist(#>=(Pivot), Prefix),
   E #> Pivot,
   length([_|Prefix], Index).           % 1-based index

Sample queries using SICStus Prolog 4.3.3:

| ?- zs_first_greater([1,1,1,2,1,1], I, 1).
I = 4 ? ;
no

| ?- zs_first_greater([1,1,1,2,1,1], I, 3).
no

| ?- zs_first_greater([], I, 3).
no

| ?- zs_first_greater([1,1,1,1,5,1,1,2], I, 1).
I = 5 ? ;
no

Thanks to we can also ask very general queries:

| ?- zs_first_greater([A,B,C,D], I, X).
I = 1,
A#>=X+1,
A in inf..sup,
X in inf..sup ? ;
I = 2,
A#=<X,
B#>=X+1,
A in inf..sup,
X in inf..sup,
B in inf..sup ? ;
I = 3,
A#=<X,
B#=<X,
C#>=X+1,
A in inf..sup,
X in inf..sup,
B in inf..sup,
C in inf..sup ? ;
I = 4,
A#=<X,
B#=<X,
C#=<X,
D#>=X+1,
A in inf..sup,
X in inf..sup,
B in inf..sup,
C in inf..sup,
D in inf..sup ? ;
no
1
votes

To get any index in L, holding an element V greater than N, you could write:

?- L=[1,2,3,1,2,3],N=2, nth1(I,L,V),V>N.

and to limit to first instance:

?- L=[1,2,3,1,2,3],N=2, once((nth1(I,L,V),V>N)).

If you have library(clpfd) available, and your list has domain limited to integers, element/3 can play the same role as nth1/3, giving a bit more of generality

0
votes

Here's a solution, as others pointed out it's not general, it will only work if the List of integers and the Threshold are ground terms.

As with most list processing predicates we need to think about it recursively:

  1. Check the header of the list (its first element). If it's greater than the provided threshold then we are done.
  2. Otherwise apply step 1. to the tail of the list (the list that remains after removing the header).

As you want the index of the element (as opposed to its actual value), we also need to keep track of the index and increment it in step 2. To do that we'll need a helper predicate.

%
% Predicate called by the user:
%
% The element of List at Index is the first one greater than Threshold.
%
idx_first_greater(List, Threshold, Index) :-
   % here we use our helper predicate, initializing the index at 1.
   idx_first_greater_rec(List, Threshold, 1, Index).

%
% Helper predicate:
%
% idx_first_greater_rec(List, Threshold, CurIdx, FoundIdx) :
%    The element of List at FoundIndex is the first one greater
%    than Threshold. FoundIdx is relative to CurIdx.
%

% Base case. If the header is greater than the Threshold then we are done.
% FoundIdx will be unified with CurIdx and returned back to the recursion stack.
idx_first_greater_rec([H|_], Threshold, Index, Index) :- H > Threshold, !.

% Recursion. Otherwise increment CurIdx and search in the tail of the list
idx_first_greater_rec([_|T], Threshold, CurIdx, FoundIdx) :-
   NewIdx is CurIdx+1,
   idx_first_greater_rec(T, Threshold, NewIdx, FoundIdx).

Notes:

  1. The predicate will fail if the empty list is passed or if no element greater than Threshold was found. This looks to me like a good behavior.
  2. This solution is tail-recursive, so it can be optimized by Prolog automatically.

Sample output:

?- idx_first_greater([1,1,1,2,1,1], 1, Idx).
Idx = 4 ;
false.

?- idx_first_greater([1,1,1,2,1,1], 3, Idx).
false.

?- idx_first_greater([], 3, Idx).
false.