3

I'm having an issue with SWI-Prolog's delete/3 predicate. The easiest way is just a quick example:

?- delete([(1,1),(1,2),(3,2)], (1,_), List).
List = [(1,2),(3,2)].

I would expect (1,2) to also be deleted, since (1,_) unifies with (1,2). The SWIPL help says:

Delete all members of List1 that simultaneously unify with Elem and unify the result with List2.

Why is this and how can I delete everything that unifies with (1,_)?

repeat
  • 18,496
  • 4
  • 54
  • 166
HDW
  • 308
  • 2
  • 14

3 Answers3

3

" Delete all members of List1 that simultaneously unify with Elem and unify the result with List2."

(1,X) first unifies with (1,1). therefore, X is unified with 1 and cannot be unified with 2 to delete (1,2). so the problem is not that it does not delete all of the members; it's that it doesnt unify simultaneously with (1,2) and (1,1) (try delete([(1,1),(1,2),(1,1),(3,2)],(1,_),List).

btw, according to the swi-prolog manual:

delete(?List1, ?Elem, ?List2)
Is true when Lis1, with all occurences of Elem deleted results in List2.

also, delete/3 is deprecated:

There are too many ways in which one might want to delete elements from a list to justify the name. Think of matching (= vs. ==), delete first/all, be deterministic or not.

So the easiest way is to write your own predicate. Something like:

my_delete(Pattern,[Pattern|T],TD):-
   my_delete(Pattern,T,TD).
my_delete(Pattern,[H|T],[H|TD]):-
   my_delete(Pattern,T,TD).

perhaps?

check exclude/3, include/3, partition/4

Thanos Tintinidis
  • 5,828
  • 1
  • 20
  • 31
2

Use texclude/3 in combination with the reified term equality predicate (=)/3!

First, we try using (=)/3 directly...

?- texclude(=((1,V)), [(1,1),(1,2),(3,2)], KVs).
KVs = [      (1,2),(3,2)],     V=1            ;
KVs = [(1,1),      (3,2)],               V=2  ;
KVs = [(1,1),(1,2),(3,2)], dif(V,1), dif(V,2).

Not quite! For our next tries we are going to use lambda expressions.

:- use_module(library(lambda)).

Let's query---once with texclude/3, once with tinclude/3, and once with tpartition/4:

?- texclude(  \ (K,_)^(K=1), [(1,1),(1,2),(3,2)], Fs).
Fs = [(3,2)].                                     % succeeds deterministically

?- tinclude(  \ (K,_)^(K=1), [(1,1),(1,2),(3,2)], Ts).
Ts = [(1,1),(1,2)].                               % succeeds deterministically

?- tpartition(\ (K,_)^(K=1), [(1,1),(1,2),(3,2)], Ts,Fs).
Ts = [(1,1),(1,2)], Fs = [(3,2)].                 % succeeds deterministically

Alright! Do we get the same solutions if the list items are bound after the texclude/3 call?

?- texclude(\ (K,_)^(K=1), [A,B,C], Fs), A = (1,1), B = (1,2), C = (3,2).
A = (1,1), B = (1,2), C = (3,2), Fs = [(3,2)] ;   % succeeds with choice point
false.

Yes! At last, consider the following quite general query:

?- texclude(\ (K,_)^(K=1), [A,B], Fs).
Fs = [   ], A = (  1,_A1), B = (  1,_B1)                         ;
Fs = [  B], A = (  1,_A1), B = (_B0,_B1),             dif(_B0,1) ;
Fs = [A  ], A = (_A0,_A1), B = (  1,_B1), dif(_A0,1)             ;
Fs = [A,B], A = (_A0,_A1), B = (_B0,_B1), dif(_A0,1), dif(_B0,1).

Note that above goals restrict all list items to have the form (_,_). Thus the following query fails:

?- texclude(\ (K,_)^(K=1), [x,_], _).
false.
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
1

This answer tries to generalize the idea presented in previous answer.

Let's define a reified variant of subsumes_term/2:

list_nonvardisj([A],C) :- 
   !, 
   C = nonvar(A).
list_nonvardisj([A|As],(nonvar(A);C)) :-
   list_nonvardisj(As,C).

subsumes_term_t(General,Specific,Truth) :-
   subsumes_term(General,Specific),
   !,
   term_variables(General,G_vars),
   free4evrs(G_vars),
   Truth = true.
subsumes_term_t(General,Specific,Truth) :-
   Specific \= General,
   !,
   Truth = false.
subsumes_term_t(General,Specific,Truth) :-
   term_variables(Specific,S_vars),
   (  S_vars = [V]
   -> freeze(V,subsumes_term_t(General,Specific,Truth))
   ;  S_vars = [_|_]
   -> list_nonvardisj(S_vars,S_wakeup),
      when(S_wakeup,subsumes_term_t(General,Specific,Truth))
   ;  throw(error(instantiation_error, subsumes_term_t/3))
   ),
   (  Truth = true
   ;  Truth = false
   ).

The above definition of the reified predicate subsumes_term_t/3 uses free4evrs/1 to ensure that the "generic" term passed to subsumes_term/2 is not instantiated any further.

For SICStus Prolog, we can define it as follows:

:- module(free4evr,[free4evr/1,free4evrs/1]).

:- use_module(library(atts)).

:- attribute nvrb/0.                       % nvrb ... NeVeR Bound

verify_attributes(V,_,Goals) :-
   get_atts(V,nvrb), 
   !,
   Goals = [throw(error(uninstantiation_error(V),free4evr/1))].
verify_attributes(_,_,[]).

attribute_goal(V,free4evr(V)) :-
   get_atts(V,nvrb).

free4evr(V) :-
   nonvar(V),
   !,
   throw(error(uninstantiation_error(V),free4evr/1)).
free4evr(V) :-
   (  get_atts(V,nvrb)
   -> true
   ;  put_atts(Fresh,nvrb),
      V = Fresh
   ).

free4evrs([]).
free4evrs([V|Vs]) :-
   free4evr(V),
   free4evrs(Vs).

Let's put subsumes_term_t/3 to use!

?- texclude(subsumes_term_t(1-X), [A,B,C], Fs), A = 1-1, B = 1-2, C = 3-2.
A = 1-1, B = 1-2, C = 3-2, Fs = [C], free4evr(X) ? ;   % succeeds with choice-point
no

?- texclude(subsumes_term_t(1-X), [x,1-Y,2-3], Fs).
Fs = [x,2-3], free4evr(X) ? ;
no

What happens if we instantiate variable X in above query sometime after the call to texclude/3?

?- texclude(subsumes_term_t(1-X), [x,1-Y,2-3], Fs), X=something.
! error(uninstantiation_error(something),free4evr/1)
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166