delete only middle elements except first and last element - prolog

Example; I have a list [1,2,3,a,f,s,h,u,4,5]. I want to delete 2,3,a,f,s,h,u,4 and final result will [1,5]. How do i write predicate in Prolog?
delete(A, [A|B], B).
delete(A, [B, C|D], [B|E]) :-
delete(A, [C|D], E).

A nice way to think of sequence based problems like this is with DCG (Definite Clause Grammar) which is a standard part of most of the common Prolog distributions, such as SWI and GNU:
first_last([First, Last]) --> [First], ..., [Last].
... --> [].
... --> [_], ... .
first_and_last(L, FirstLast) :-
phrase(first_last(FirstLast), L).

First, this should be a delete/2 predicate, not a delete/3.
The base clause should be a list that has only two members, while the recursive clause should drop the second element, and move on:
delete([A,B], [A,B]).
delete([A,_|R], X) :- delete([A|R], X).
Demo.

you can use append/3:
?- X=[1,2,3,a,f,s,h,u,4,5].
X = [1, 2, 3, a, f, s, h, u, 4|...].
?- append([F|_],[L],$X).
F = 1,
L = 5,
X = [1, 2, 3, a, f, s, h, u, 4|...] .
or append/2
?- append([[F],_,[L]],$X).
F = 1,
L = 5,
X = [1, 2, 3, a, f, s, h, u, 4|...] .
or even a more succint version of #lurker answer:
?- [user].
|: ... --> [] | ([_], ...).
|: ^D% user://1 compiled 0.01 sec, 1 clauses
true.
?- phrase(([F],...,[L]),$X).
F = 1,
L = 5,
X = [1, 2, 3, a, f, s, h, u, 4|...] ;
false.

Related

output a binary tree in preorder as a list in prolog

I am trying to create a list as output for a binary tree in prolog here is my code so far.
preorder(node(R, empty, empty),[R]).
preorder(node(R,Lb,Rb),[R|Ys]) :- preorder(Lb, Ys).
preorder(node(R,Lb,Rb),[R|Ys]) :-preorder(Rb, Ys).
My thought being that you traverse the tree and add the R to the rest list Ys.
it doesnt work as intendet though
?- preorder(node(1,node(2,empty,empty),node(3,empty,empty)),Z).
Z = [1, 2] ;
Z = [1, 3] ;
false.
This is the query I try to run and what I get. Prolog gives me all possible ways to the leafs, but I want just one list with all values in preorder, so basically the 2 lists combined([1,2,3]).
You can use the following code:
preorder(T, L) :-
preorder(T, [], L).
preorder(empty, L, L).
preorder(node(R, Lb, Rb), L0, [R|L2]) :-
preorder(Rb, L0, L1),
preorder(Lb, L1, L2).
Examples:
?- preorder(node(1,node(2,empty,empty),node(3,empty,empty)), L).
L = [1, 2, 3].
?- preorder(empty, L).
L = [].
?- preorder(node(1, empty, empty), L).
L = [1].
?- preorder(node(1,node(2,node(3,empty,empty),node(4,empty,empty)),node(5,empty,empty)), L).
L = [1, 2, 3, 4, 5].

How to use an fd solver to determine which elements of a list can sum to a given number?

Given a list of possible summands I want to determine which, if any, can form a given sum. For example, with [1,2,3,4,5] I can make the sum of 9 with [4,5], [5,3,1], and [4,3,2].
I am using GNU Prolog and have something like the following which does not work
numbers([1,2,3,4,5]).
all_unique(_, []).
all_unique(L, [V|T]) :-
fd_exactly(1, L, V),
all_unique(L, T).
fd_sum([], Sum).
fd_sum([H|T], Sum):-
S = Sum + H,
fd_sum(T, S).
sum_clp(N, Summands):-
numbers(Numbers),
length(Numbers, F),
between(1, F, X),
length(S, X),
fd_domain(S, Numbers),
fd_domain(Y, [N]),
all_unique(S, Numbers),
fd_sum(S, Sum),
Sum #= Y,
fd_labeling(S).
I think the main problem is that I am not representing the constraint on the sum properly? Or maybe it is something else?
Just in case you're really interested in CLP(FD), here is your corrected program.
numbers([1,2,3,4,5]).
% note: use builtins where available, both for efficiency and correctness
%all_unique(_, []).
%all_unique(L, [V|T]) :-
% fd_exactly(1, L, V),
% all_unique(L, T).
fd_sum([], 0). % sum_fd_SO.pl:8: warning: singleton variables [Sum] for fd_sum/2
fd_sum([H|T], Sum):-
% note: use CLP(FD) operators and the correct operands
Sum #= S + H,
fd_sum(T, S).
sum_clp(N, S):- % sum_fd_SO.pl:13-23: warning: singleton variables [Summands] for sum_clp/2
numbers(Numbers),
length(Numbers, F),
between(1, F, X),
length(S, X),
fd_domain(S, Numbers),
%fd_domain(Y, [N]),
%all_unique(S, Numbers),
fd_all_different(S),
fd_sum(S, N),
%Sum #= Y,
fd_labeling(S).
test
?- sum_clp(3,L).
L = [3] ? ;
L = [1,2] ? ;
L = [2,1] ? ;
no
I think mixing the code for sublist into clp code is causing some confusion. GNU-Prolog has a sublist/2 predicate, you can use that.
You seem to be building the arithmetic expression with fd_sum but it is incorrectly implemented.
sum_exp([], 0).
sum_exp([X|Xs], X+Xse) :-
sum_exp(Xs, Xse).
sum_c(X, N, Xsub) :-
sublist(Xsub, X),
sum_exp(Xsub, Xe),
N #= Xe.
| ?- sum_exp([A, B, C, D], X).
X = A+(B+(C+(D+0)))
yes
| ?- sum_c([1, 2, 3, 4, 5], 9, X).
X = [4,5] ? ;
X = [2,3,4] ? ;
X = [1,3,5] ? ;
(1 ms) no
| ?- length(X, 4), sum_c(X, 4, [A, B]), member(A, [1, 2, 3]).
A = 1
B = 3
X = [_,_,1,3] ? ;
A = 2
B = 2
X = [_,_,2,2] ? ;
A = 3
B = 1
X = [_,_,3,1] ?
yes

Tail-recursive program in prolog which outputs odd numbers in a list

I've written a tail-recursive predicate in Prolog which outputs the integers between A and B in a list K. I've used "reverse" to bring the numbers into the right order:
numbers(A,B,K) :- numbers(A,B,[],K).
numbers(Y,Y,X,K) :- !, reverse([Y|X],K).
numbers(A,B,X,K) :- A<B, C is A+1, numbers(C,B,[A|X],K).
Query:
?- numbers(3,6, K).
K=[3,4,5,6]
All works fine. What I now want to do is that I only want to have odd numbers of the range between A and B in the list K. How can I do that? Thanks in advance!
Firstly, I would try to avoid using reverse/2. If you have such a solution, it's often an indicator that there's a better way to get the answer forwards more directly. Not always, but most often. reverse/2 is probably the 2nd favorite band-aid in Prolog right behind use of the cut. :)
In many problems, an auxiliary accumulator is needed. In this particular case, it is not. Also, I would tend to use CLP(FD) operations when involving integers since it's the more relational approach to reasoning over integers. But you can use the solution below with is/2, etc, if you wish. It just won't be as general.
numbers(S, E, []) :- S #> E. % null case
numbers(X, X, [X]).
numbers(S, E, [S|T]) :-
S #< E,
S1 #= S + 1,
numbers(S1, E, T).
| ?- numbers(3, 8, L).
L = [3,4,5,6,7,8] ? ;
no
| ?- numbers(A, B, [2,3,4,5]).
A = 2
B = 5 ? ;
no
| ?-
This solution avoids reverse/2 and is tail recursive.
To update it for odd integers, the first thought is that we can easily modify the above to do every other number by just adding 2 instead of 1:
every_other_number(S, E, []) :- S #> E.
every_other_number(X, X, [X]).
every_other_number(S, E, [S|T]) :-
S #< E,
S1 #= S + 2,
every_other_number(S1, E, T).
| ?- every_other_number(3, 7, L).
L = [3,5,7] ? ;
no
| ?- every_other_number(3, 8, L).
L = [3,5,7] ? ;
no
| ?- every_other_number(4, 8, L).
L = [4,6,8] ? ;
no
| ?-
Then we can do odd numbers by creating an initial predicate to ensure the condition that the first value is odd and calling every_other_number/3:
odd_numbers(S, E, L) :-
S rem 2 #= 1,
every_other_number(S, E, L).
odd_numbers(S, E, L) :-
S rem 2 #= 0,
S1 #= S + 1,
every_other_number(S1, E, L).
| ?- odd_numbers(2, 8, L).
L = [3,5,7] ? ;
no
| ?- odd_numbers(2, 9, L).
L = [3,5,7,9] ? ;
no
| ?- odd_numbers(3, 8, L).
L = [3,5,7] ? ;
no
| ?-
This could be a solution, using mod/2 operator.
numbers(A,B,K) :-
B1 is B+1,
numbers(A,B1,[],K).
numbers(Y,Y1,X,K) :-
Y = Y1,
reverse(X,K).
numbers(A,B,X,K) :-
A<B,
C is A+1,
C1 is mod(C,2),
(C1 = 0 ->
numbers(C,B,[A|X],K)
; numbers(C,B,X,K)).
Another possibility is to use DCG :
numbers(A,B,K) :-
phrase(odd(A,B), K).
odd(A,B) --> {A > B, !}, [].
odd(A,B) --> {A mod2 =:= 0, !, C is A+1}, odd(C,B).
odd(A,B) --> {C is A+2}, [A], odd(C, B).

Prolog replace each instance of a constant in a list with a variable

Given list of constants, how can you replace each instance of a constant with a variable? Like so:
[1,1,2,1,2,3]
=
[A,A,B,A,B,C]
This is my version:
f([],Seen0,Out,Out) :-
write(Seen0).
f([H|T],Seen0,Out0,Out):-
member(H/Var0,Seen0),
append(Out0,[Var0],Out1),
f(T,Seen0,Out1,Out).
f([H|T],Seen0,Out0,Out):-
not(member(H/Var,Seen0)),
append(Seen0,[H/Var],Seen1),
append(Out0,[Var],Out1),
f(T,Seen1,Out1,Out).
And runs like so:
?- f([1,1,2,1,2,3],[],[],O).
[1/_G31,2/_G58,3/_G118]
O = [_G31, _G31, _G58, _G31, _G58, _G118] .
And:
?- f([a,a,b,a,b,c],[],[],O).
[a/_G311,b/_G338,c/_G398]
O = [_G311, _G311, _G338, _G311, _G338, _G398]
Any other (better?) solutions?
A bit simpler:
ints_vars([], [], _).
ints_vars([I|Is], [V|Vs], Map) :-
once(member(I/V, Map)),
ints_vars(Is, Vs, Map).
Giving:
?- ints_vars([1, 1, 2, 1, 2, 3], Vs, Map).
Vs = [_281, _281, _295, _281, _295, _315]
Map = [1 / _281, 2 / _295, 3 / _315|_321]
Yes (0.00s cpu)
to_vars(L, R) :-
pairs_keys_values(Ps, L, _),
maplist(peek(Ps), L, R).
peek(Ps, K, V) :- memberchk(K-V, Ps).
yields
?- to_vars([a,a,b,c,a],L).
L = [_G2400, _G2400, _G2418, _G2427, _G2400].
edit this one takes the idea from #jschimpf (+1) of using a free variable as 'dictionary'. Seems very clean to me...
to_vars(L, V) :- phrase(to_vars(_, V), L).
to_vars(_, []) --> [].
to_vars(Seen, [V|Vs]) --> [E], {memberchk(E-V, Seen)}, to_vars(Seen, Vs).

Swap second and prelast element from a list prolog

Well, for the last few hours, I've been trying to swap the second item of a given list with its penultimate item (the second last). Give the list [a,b,c,d,e,f], I want to get [a,e,c,d,b,f]. For example:
correct(List1,X,List2)
?-correct([a,y,b,c,d,e,x,f],x,List2).
List2[a,x,b,c,d,e,y,f].
List1 is the list i got to swap second and penultimate (second last) element.
X is the penultimate element.
List2 is the new list with the swapped elements.
The solutions posted by mbratch and CapelliC both fail for the following base case:
?- correct([a,y], X, List2).
false.
The following solution takes care of this base case and doesn't rely on list predicates that may or may not be available. It traverses the list once and is more efficient than the other two solutions:
correct([PreLast, Second], Second, [Second, PreLast]) :-
!.
correct([First, Second, Last], Second, [First, Second, Last]) :-
!.
correct([First, Second| InRest], PreLast, [First, PreLast| OutRest]) :-
correct_aux(InRest, Second, PreLast, OutRest).
correct_aux([PreLast, Last], Second, PreLast, [Second, Last]) :-
!.
correct_aux([Other| InRest], Second, PreLast, [Other| OutRest]) :-
correct_aux(InRest, Second, PreLast, OutRest).
Sample queries:
?- correct([a,b], X, List).
X = b,
List = [b, a].
?- correct([a,b,c], X, List).
X = b,
List = [a, b, c].
?- correct([a,b,c,d], X, List).
X = c,
List = [a, c, b, d].
?- correct([a,b,c,d,e], X, List).
X = d,
List = [a, d, c, b, e].
This will work for lists of length 4 or greater:
correct( [H1|[H2|T1]], X, [H1|[X|T2]] ) :-
reverse(T1, [HR|[X|TR]]),
reverse([HR|[H2|TR]], T2).
| ?- correct( [1,2,3,4,5,6], X, L ).
L = [1,5,3,4,2,6]
X = 5
(1 ms) yes
| ?-
You can include the shorter cases, if that's the intention, by adding two more predicates, bringing the solution to:
correct( [A,X], X, [X,A] ).
correct( [A,X,B], X, [A,X,B] ).
correct( [H1|[H2|T1]], X, [H1|[X|T2]] ) :-
reverse(T1, [HR|[X|TR]]),
reverse([HR|[H2|TR]], T2).
another available builtin is append/2:
3 ?- [user].
correct(L, X, R) :- append([[A,B],C,[X,E]], L), append([[A,X],C,[B,E]], R).
|:
% user://2 compiled 0.02 sec, 2 clauses
true.
4 ?- correct( [1,2,3,4,5,6], X, L ).
X = 5,
L = [1, 5, 3, 4, 2, 6] ;
I like mbratch one (+1), maybe this solution is more intuitive.

Resources