Delete vowels in a list

The following is based on the reification of term equality/inequality.

First, we first define list_memberd_t/3, which behaves just like the memberd_truth/3 but has a different argument order:

list_memberd_t([]    ,_,false).
list_memberd_t([Y|Ys],X,Truth) :-
   if_(X=Y, Truth=true, list_memberd_t(Ys,X,Truth)).

list_memberd_truth(Xs,X,Truth) :- list_memberd_t(Xs,X,Truth).

For the sake of brevity, let’s define memberd_t/3 based on list_memberd_t/3:

memberd_t(X,Xs,Truth) :- list_memberd_t(Xs,X,Truth).

As a parallel to library(apply), let’s define tinclude/3:

:- meta_predicate tinclude(2,?,?).
tinclude(P_2,Xs,Zs) :- 
    list_tinclude_list(Xs,P_2,Zs).

list_tinclude_list([],   _P_2,[]).
list_tinclude_list([E|Es],P_2,Fs0) :-
    if_(call(P_2,E), Fs0 = [E|Fs], Fs0 = Fs),
    list_tinclude_list(Es,P_2,Fs).

tfilter/3 is another name for tinclude/3:

tfilter(P_2,As,Bs) :-
   tinclude(P_2,As,Bs).

Next, we define the meta-predicate texclude/3, the opposite of tinclude/3:

:- meta_predicate texclude(2,?,?).
texclude(P_2,Xs,Zs) :- 
    list_texclude_list(Xs,P_2,Zs).

list_texclude_list([],_,[]).
list_texclude_list([E|Es],P_2,Fs0) :-
    if_(call(P_2,E), Fs0 = Fs, Fs0 = [E|Fs]),
    list_texclude_list(Es,P_2,Fs).

Now let’s use them together!

?- texclude(list_memberd_truth([a,e,i,o,u]),
            [d,e,l,e,t,e,' ',v,o,w,e,l,s,' ',i,n,' ',a,' ',l,i,s,t], Filtered).
Filtered  = [d,  l,  t,  ' ',v,  w,  l,s,' ',  n,' ',  ' ',l,  s,t].

Edit

As an alternative to using above texclude/3, let’s use tinclude/3 with an auxiliary predicate not/3 to flip the truth value:

:- meta_predicate not(2,?,?).
not(P_2,X,Truth) :-
   call(P_2,X,Truth0),
   truth_flipped(Truth0,Truth).

truth_flipped(true,false).
truth_flipped(false,true).

Sample query:

?- tinclude(not(list_memberd_truth([a,e,i,o,u])),
            [d,e,l,e,t,e,' ',v,o,w,e,l,s,' ',i,n,' ',a,' ',l,i,s,t], Filtered).
Filtered  = [d,  l,  t,  ' ',v,  w,  l,s,' ',  n,' ',  ' ',l,  s,t].

Leave a Comment