1

I'm trying to create a rule F(C,L) where C and L are integer lists. L contains the index number (starting from 1) of all the elements of C that are equal to 43. My code is shown below. When I try F([43,42,43,42,42,43],L). it returns true. What have I done wrong? Thanks in advance!

F(C,L) :-
    forall(
        (
            member(X,C),
            X=43,
            nth1(N,C,X)
        ),
        member(N,L)
    ).
Willem Van Onsem
  • 443,496
  • 30
  • 428
  • 555
George
  • 23
  • 3
  • 5
    Prolog predicate cannot start with a capital letter, So the code you're showing must generate an error and not even run. – lurker Jul 02 '16 at 17:46

4 Answers4

3

The code by @CapelliC works, but only when used with sufficient instantiation.

?- f([43,42,43,42,42,43], Ps).
Ps = [1,3,6].                              % ok

?- f([A,B], Ps).
Ps = [1,2].                                % BAD

?- f(_, _).
**LOOPS**                                  % BAD: doesn't terminate

To safeguard against problems like these we can use iwhen/2 like so:

f_safe(C, L) :-
   iwhen(ground(C), findall(X,nth1(X,C,43),L)).

Let's re-run above queries with SWI-Prolog:

?- f_safe([43,42,43,42,42,43], Ps).
Ps = [1,3,6].                              % still ok

?- f_safe([A,B], Ps).                      % BETTER
ERROR: Arguments are not sufficiently instantiated

?- f_safe(_, _).                           % BETTER
ERROR: Arguments are not sufficiently instantiated
repeat
  • 18,496
  • 4
  • 54
  • 166
2

Syntax error apart, you're doing it more complex than needed. Keep it simpler, and use findall/3 instead of forall/2. The latter cannot be used to instantiate variables outside its scope.

f(C,L) :- findall(X, nth1(X,C,43), L).
CapelliC
  • 59,646
  • 5
  • 47
  • 90
2

Take it step by step:

:- use_module(library(clpfd)).

list_contains_at1s(Elements, Member, Positions) :-
   list_contains_at_index1(Elements, Member, Positions, 1).

list_contains_at_index1([], _, [], _).
list_contains_at_index1([E|Es], E, [I1|Is], I1) :-
   I2 #= I1+1,
   list_contains_at_index1(Es, E, Is, I2).
list_contains_at_index1([E|Es], X, Is, I1) :-
   dif(X, E),
   I2 #= I1+1,
   list_contains_at_index1(Es, X, Is, I2).

Sample query with SWI-Prolog:

?- list_contains_at1s([43,42,43,42,42,43], 43, Positions).
   Positions = [1,3,6]
;  false.                                % left-over choicepoint
repeat
  • 18,496
  • 4
  • 54
  • 166
2

While this previous answer preserves , it shows some inefficiency in queries like:

?- list_contains_at1s([43,42,43,42,42,43], 43, Ps).
Ps = [1,3,6] ;       % <------ SWI toplevel indicates lingering choicepoint
false.

In above query the lingering choicepoint is guaranteed to be useless: we know that above use case can never yield more than one solution.

Method 1: explicit indexing and extra helper predicate

The earlier definition of list_contains_at_index1/4 has two recursive clauses—one covering the "equal" case, the other one covering the "not equal" case.

Note that these two recursive clauses of list_contains_at_index1/4 are mutually exclusive, because (=)/2 and dif/2 are mutually exclusive.

How can we exploit this?

By utilizing first-argument indexing together with the reified term equality predicate (=)/3!

:- use_module(library(reif)).

list_contains_at_index1([], _, [], _).
list_contains_at_index1([E|Es], X, Is0, I1) :-
   =(E, X, T),                              % (=)/3
   equal_here_at0_at(T, I1, Is0, Is),
   I2 #= I1+1,
   list_contains_at_index1(Es, X, Is, I2).

equal_here_at0_at(true , I1, [I1|Is], Is).  % index on the truth value ...
equal_here_at0_at(false,  _,     Is , Is).  % ... of reified term equality

Method 2: implicit indexing, no extra helper predicate, using if_/3

For more concise code we can put if_/3 to good use:

list_contains_at_index1([], _, [], _).
list_contains_at_index1([E|Es], X, Is0, I1) :-
   if_(E = X, Is0 = [I1|Is], Is0 = Is),
   I2 #= I1+1,
   list_contains_at_index1(Es, X, Is, I2).

If we re-run above query with new improved code ...

?-  list_contains_at1s([43,42,43,42,42,43], 43, Positions).
Positions = [1, 3, 6].

... we see that the query now succeeds deterministically. Mission accomplished!

Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166