3

I am searching some predicate:

reduce_2n_invariant(+I, +F, -O)

based on:

  • some input list I
  • some input operator F of form fx,

which generates some output list O, that satisfies following general condition:

∀x:(x ∈ O ↔ ∀ n ∈ ℕ ∀ y ∈ O: x ≠ F(F(...F(y)...)),

whereby F is applied 2 times n times to y.

Is their some easy way to do that with swi-prolog?

E.g. the list

l = [a, b, f(f(a)), f(f(c)),  f(f(f(a))), f(f(f(f(a)))), f(b),f(f(b))] 

with operator f should result in:

O = [a, b, f(f(c)), f(f(f(a))), f(b)]

My code so far:

invariant_2(X, F, Y) :-
    Y = F(F(X)).
invariant_2(X, F, Y) :-
    Y = F(F(Z)), invariant_2(X, F, Z).

reduce_2n_invariant(LIn, F, LOut) :-
    findall(X, (member(X, LIn), forall(Y, (member(Y, LIn), not(invariant(Y,F,X))))), LOut).

leads to an error message:

/test.pl:2:5: Syntax error: Operator expected
/test.pl:4:5: Syntax error: Operator expected

after calling:

invariant_2(a,f,f(f(a))).
false
  • 10,264
  • 13
  • 101
  • 209
Martin Kunze
  • 995
  • 6
  • 16
  • If I understand correctly, `O` is supposed to contain only those members of `I` with odd applications of `F` in the same order. Is this correct? – lambda.xy.x Apr 22 '22 at 18:06
  • In that case the first exercise could be to write a predicate `odd_apps(F, Term)` which if true exactly if `Term` is an odd application of `F` terms. The base case would be any constants, functions of different functors and applications of `F` that don't contain `F` on the next level. The predicate `dif/2` might come in handy there. – lambda.xy.x Apr 22 '22 at 18:11

2 Answers2

3

The error message is due to the fact that Prolog does not accept terms with variable functors. So, for example, the goal Y2 = F(F(Y0)) should be encoded as Y2 =.. [F,Y1], Y1 =.. [F,Y0]:

?- F = f, Y2 = f(f(f(a))), Y2 =.. [F,Y1], Y1 =.. [F,Y0].
F = f,
Y2 = f(f(f(a))),
Y1 = f(f(a)),
Y0 = f(a).

A goal of the form Term =.. List (where the ISO operator =.. is called univ) succeeds if List is a list whose first item is the functor of Term and the remaining items are the arguments of Term. Using this operator, the predicate invariant_2/3 can be defined as follows:

invariant_2(X, F, Y2) :-
    (   Y2 =.. [F, Y1],
        Y1 =.. [F, Y0]
    ->  invariant_2(X, F, Y0)
    ;   Y2 = X ).

Examples:

?- invariant_2(a, f, f(f(a))).
true.

?- invariant_2(a, f, f(f(f(a)))).
false.

?- invariant_2(g(a), f, f(f(g(a)))).
true.

?- invariant_2(g(a), f, f(f(f(g(a))))).
false.

The specification of reduce_2n_invariant/3 is not very clear to me, because it seems that the order in which the input list items are processed may change the result obtained. Anyway, I think you can do something like this:

reduce_2n_invariant(Lin, F, Lout) :-
    reduce_2n_invariant_loop(Lin, F, [], Lout).

reduce_2n_invariant_loop([], _, Lacc, Lout) :-
    reverse(Lacc, Lout).

reduce_2n_invariant_loop([X|Xs], F, Lacc, Lout) :-
    (   forall(member(Y, Lacc), not(invariant_2(Y, F, X)))
    ->  Lacc1 = [X|Lacc]
    ;   Lacc1 = Lacc ),
    reduce_2n_invariant_loop(Xs, F, Lacc1, Lout).

Example:

?- reduce_2n_invariant([a,b,f(f(a)),f(f(c)),f(f(f(a))),f(f(f(f(a)))),f(b),f(f(b))], f, Lout).
Lout = [a, b, f(f(c)), f(f(f(a))), f(b)].
slago
  • 5,025
  • 2
  • 10
  • 23
2

@slago beat me by a few minutes but since I've already written it, I'll still post it:

I'm shying away from the findall because the negation of the invariant is very hard to express directly. In particular, terms compared by the invariant must be ground for my implementation (e.g. [f(a), f(g(f(a)))] should not lose any terms but [f(a), f(f(f(a)))] should reduce to [f(a)] which means that the base case of the definition can't just pattern match on the shape of the parameter in the case two terms are not in this relation).

The other problem was already explained, in that F=f, X=F(t) is not syntactically correct and we need the meta-logical =.. to express this.

term_doublewrapped_in(X, Y, Fun) :-
    Y =.. [Fun, T],
    T =.. [Fun, X].
term_doublewrapped_in(X, Y, Fun) :-
    Y =.. [Fun, T],
    T =.. [Fun, Z],
    term_doublewrapped_in(X, Z, Fun).

Apart from term_doublewrapped_in not necessarily terminating when the second parameter contains variables, it might also give rise to false answers due to the occurs check being disabled by default:

?- term_doublewrapped_in(X, f(X), F).
X = f(X),    % <-- cyclic term here
F = f ;
% ...

Therefore the groundness condition is actually required for the soundness of this procedure.

I just lifted this notion to lists:

anymember_doublewrapped_in(Terms, X, F) :-
    member(T, Terms),
    term_doublewrapped_in(T,X,F).

and wrapped it into a variant of filter/3 that negates the predicate given:

functor_list_reduced_acc(_F, _L, [], []).
functor_list_reduced_acc(F, L, R, [X|Xs]) :-
    anymember_doublewrapped_in(L, X, F)
    -> functor_list_reduced_acc(F, L, R, Xs)
    ;  ( R = [X|Rs], functor_list_reduced_acc(F, L, Rs, Xs) ).

functor_list_reduced(F,L,R) :-
    functor_list_reduced_acc(F,L,R,L).

I first tried using partiton/4 to do the same but then we would need to include library(lambda) or a similar implementation to make dynamically instantiate the invariant to the correct F and list element.

lambda.xy.x
  • 4,918
  • 24
  • 35