Delete vowels in a list
Asked Answered
A

3

1

Write a program that deletes vowels (String, NoVowelsString) that deletes all vowels from a given string.

So far I've got the condition vowel(X):- member(X,[a,e,i,o,u]). Then I thought of the one that deletes all the elements from the other list:

delete2([],L1,L1).
delete2([H|T],L1,L3) :-
   delete2(H,L1,R2),
   delete2(T,R2,L3).

So having these two I thought that I could put a condition to those elements being deleted that they have to be a member of [a,e,i,o,u]. Though I still haven't got anywhere.

Altman answered 21/11, 2012 at 10:12 Comment(0)
V
0

Here is the code

deleteV([H|T],R):-member(H,[a,e,i,o,u]),deleteV(T,R),!.
deleteV([H|T],[H|R]):-deleteV(T,R),!.
deleteV([],[]).

What it does? First it question itself?It's the head a vowel Yes->We ignore it. No->We need it. If it finds an empty list, it constructs the result list, and when returning from backtracking it appends the consonats in front. This code was tested in SWIProlog.

Vulgate answered 23/11, 2012 at 23:51 Comment(1)
I didn't know about the strings in Prolog.Thank you.Vulgate
P
4

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].
Preterition answered 30/4, 2015 at 9:5 Comment(3)
Isn't it better to use a clean form of negation instead?Danner
@false. What is the alternative? Describing the set directly?Preterition
tfilter(not(list_memberd_truth([a,e,i,o,u])), Xs, Ys). with an appropriate definition of not/2.Danner
J
1

here a solution using DCG. Note how the 'output' is obtained (no arguments passing, only difference lists)

novowels --> ("a";"e";"i";"o";"u"), !, novowels.
% or ..
% novowels --> [C], {memberchk(C, "aeiou")}, !, novowels.
novowels, [C] --> [C], !, novowels.
novowels --> [].

I must confess the second cut doesn't like me, but seems required.

test:

?- phrase(novowels, "abcdefghilmnopq", L),format('~s',[L]).
bcdfghlmnpq
L = [98, 99, 100, 102, 103, 104, 108, 109, 110|...].

edit About the second cut, it seems required by 'left hand' notation: if I code with argument, without cut, I get a correct parsing:

novowels(Cs) --> ("a";"e";"i";"o";"u"), !, novowels(Cs).
% novowels(Cs) --> [C], {memberchk(C, "aeiou")}, !, novowels(Cs).
novowels([C|Cs]) --> [C], novowels(Cs).
novowels([]) --> [].

test:

?- phrase(novowels(L), "abcdefghilmnopq"),format('~s',[L]).
bcdfghlmnpq
L = [98, 99, 100, 102, 103, 104, 108, 109, 110|...] ;
false.

I wonder if this is a bug of the DCG translator, or (more probably) my fault...

Jacket answered 25/11, 2012 at 10:10 Comment(0)
V
0

Here is the code

deleteV([H|T],R):-member(H,[a,e,i,o,u]),deleteV(T,R),!.
deleteV([H|T],[H|R]):-deleteV(T,R),!.
deleteV([],[]).

What it does? First it question itself?It's the head a vowel Yes->We ignore it. No->We need it. If it finds an empty list, it constructs the result list, and when returning from backtracking it appends the consonats in front. This code was tested in SWIProlog.

Vulgate answered 23/11, 2012 at 23:51 Comment(1)
I didn't know about the strings in Prolog.Thank you.Vulgate

© 2022 - 2024 — McMap. All rights reserved.