Getting the product of a list from left to right - prolog

How do you get the product of a list from left to right?
For example:
?- product([1,2,3,4], P).
P = [1, 2, 6, 24] .
I think one way is to overload the functor and use 3 arguments:
product([H|T], Lst) :- product(T, H, Lst).
I'm not sure where to go from here.

You can use library(lambda) found here : http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/lambda.pl
Quite unreadable :
:- use_module(library(lambda)).
:- use_module(library(clpfd)).
product(L, R) :-
foldl(\X^Y^Z^(Y = []
-> Z = [X, [X]]
; Y = [M, Lst],
T #= X * M,
append(Lst, [T], Lst1),
Z = [T, Lst1]),
L, [], [_, R]).
Thanks to #Mike_Hartl for his advice, the code is much simple :
product([], []).
product([H | T], R) :-
scanl(\X^Y^Z^( Z #= X * Y), T, H, R).

seems like a list copy, just multiplying by last element handled. Let's start from 1 for the leftmost element:
product(L, P) :-
product(L, 1, P).
product([X|Xs], A, [Y|Ys]) :-
Y is X * A,
product(Xs, Y, Ys).
product([], _, []).
if we use library(clpfd):
:- [library(clpfd)].
product([X|Xs], A, [Y|Ys]) :-
Y #= X * A,
product(Xs, Y, Ys).
product([], _, []).
it works (only for integers) 'backward'
?- product(L, [1,2,6,24]).
L = [1, 2, 3, 4].

Probably very dirty solution (I am new to Prolog):
product([ListHead|ListTail], Answer) :-
product_acc(ListTail, [ListHead], Answer).
product_acc([ListHead|ListTail], [AccHead|AccTail], Answer) :-
Product is ListHead * AccHead,
append([Product, AccHead], AccTail, TempList),
product_acc(ListTail, TempList, Answer).
product_acc([], ReversedList, Answer) :-
reverse(ReversedList, Answer).
So basically at the beginning we call another predicate which has
extra "variable" Acc which is accumulator list.
So we take out head (first number) from original list and put it in
to Accumulator list.
Then we always take head (first number) from original list and
multiply it with head (first number) from accumulator list.
Then we have to append our new number which we got by multiplying
with the head from accumulator and later with the tail
Then we call same predicate again until original list becomes empty
and at the end obviously we need to reverse it.
And it seems to work
?- product([1,2,3,4], L).
L = [1, 2, 6, 24].
?- product([5], L).
L = [5].
?- product([5,4,3], L).
L = [5, 20, 60].
Sorry if my explanation is not very clear. Feel free to comment.

Related

How to fix this permutation sort?

The following Prolog program defines a predicate sorted/2 for sorting by permutation (permutation sort) in ascending order a list passed in first argument, which results in the list passed in second argument:
sorted(X, Y) :-
permuted(X, Y),
ordered(Y).
permuted([], []).
permuted(U, [V|W]) :-
permuted(X, W),
deleted(V, U, X).
deleted(X, [X|Y], Y).
deleted(U, [V|W], [V|X]) :-
deleted(U, W, X).
ordered([]).
ordered([_]).
ordered([X, Y|Z]) :-
ordered([Y|Z]), X =< Y.
How to solve the following issues?
The program duplicates solutions for queries in which a list with duplicate elements is passed in second argument:
?- sorted(X, [1, 1, 2]).
X = [1, 1, 2]
; X = [1, 1, 2]
; X = [1, 2, 1]
; X = [1, 2, 1]
; X = [2, 1, 1]
; X = [2, 1, 1]
; false.
The program exhausts resources for queries in which a free variable is passed in second argument:
?- sorted([2, 1, 1], Y).
Y = [1, 1, 2]
; Y = [1, 1, 2]
;
Time limit exceeded
The Prolog program is based on the Horn clause program given at section 11 of Robert Kowalski’s famous paper Predicate Logic as Programming Language:
To solve non-termination, you can add same_length/2 to sorted/2 as #false suggested:
sorted(X, Y) :-
same_length(X, Y),
permuted(X, Y),
ordered(Y).
same_length([], []).
same_length([_|Xs], [_|Ys]) :-
same_length(Xs, Ys).
Or you may embed it into permuted/2 by adding a new argument:
sorted(X, Y) :-
permuted(X, X, Y),
ordered(Y).
permuted([], [], []).
permuted(U, [_|L1], [V|W]) :-
permuted(X, L1, W),
deleted(V, U, X).
The program will still return duplicates as it only sees one item at a time.
To solve duplication, you can either generate all permutations and discard the repeated ones (which is not efficient), or only generate distinct permutations. The following modification does the latter by taking the idea of the recursive procedure permuted/2 + deleted/2 which for each item puts it at the beginning of the list and does a recursive call on the remaining list, and changes it to another recursive procedure permuted_all/2 + deleted_all/2 which for each group of same items puts them at the beginning of the list and does a recursive call on the remaining list. This program uses difference lists for better efficiency:
sorted(X, Y) :-
same_length(X, Y),
permuted_all(X, Y),
ordered(Y).
permuted_all([], []).
permuted_all(U, [V|W]) :-
deleted_all(V, U, X, n-T, [V|W]),
permuted_all(X, T).
% deleted_all(Item, List, Remainder, n-T, Items|T)
deleted_all(_, [], [], y-[X|Xs], [X|Xs]).
deleted_all(X, [V|Y], [V|Y1], y-[X|Xs], Xs1) :-
dif(X, V),
deleted_all(X, Y, Y1, y-[X|Xs], Xs1).
deleted_all(X, [X|Y], Y1, _-Xs, Xs1) :-
deleted_all(X, Y, Y1, y-[X|Xs], Xs1).
deleted_all(U, [V|W], [V|X], n-T, Xs) :-
dif(U, V),
deleted_all(U, W, X, n-T, Xs).
Sample runs:
?- sorted(X, [1, 1, 2]).
X = [1, 2, 1]
; X = [1, 1, 2]
; X = [2, 1, 1]
; false.
?- sorted([2, 1, 1], Y).
Y = [1, 1, 2]
; false.
As per OPs comment asking for a version which does not use difference lists, here goes one which instead obtains the remainder using same_length/2 + append/3 and with added comments:
permuted_all([], []).
permuted_all(U, [V|W]) :-
deleted_all(V, U, X, n, [V|W]),
same_length(X, T), % the remaining list X has the same length as T
append(_, T, [V|W]), % T corresponds to the last items of [V|W]
permuted_all(X, T). % T is a permutation of X
% deleted_all(Item, List, Remainder, n, Items|_)
deleted_all(_, [], [], y, _). % base case
deleted_all(X, [V|Y], [V|Y1], y, Xs1) :-
% recursive step when the current item is not the one we are gathering
dif(X, V),
deleted_all(X, Y, Y1, y, Xs1).
deleted_all(X, [X|Y], Y1, _, [X|Xs1]) :-
% recursive step when the current item is the one we are gathering
deleted_all(X, Y, Y1, y, Xs1).
deleted_all(U, [V|W], [V|X], n, Xs) :-
% recursive step when we have not selected yet the item we will be gathering
dif(U, V),
deleted_all(U, W, X, n, Xs).
Your second problem can by solved by replacing first line with
sorted(X, Y) :-
permuted(X, Y),
ordered(Y),
!.
or
sorted(X, Y) :-
permuted(X, Y),
ordered(Y),
length(X, Z),
length(Y, Z).
The first one is not so easy to solve because of the implementation of this algorithm. Both 1st [1, 1, 2] and 2nd [1, 1, 2] are valid permutations since your code that generated permutations generates all permutations not unique permutations.

Get set of elements from list (Prolog)

I am trying to get a set of elements from a list in prolog, such that a query:
get_elems([1, 2, 4, 10], [a, b, c, d, e], X).
yields:
X = [a, b, d]
I would like to implement it without using the built in predicate nth.
I have tried using the following, but it does not work:
minus_one([], []).
minus_one([X|Xs], [Y|Ys]) :- minus_one(Xs, Ys), Y is X-1.
get_elems([], _, []).
get_elems(_, [], []).
get_elems([1|Ns], [A|As], Z) :- get_elems(Ns, As, B), [A|B] = Z.
get_elems(Ns, [_|As], Z) :- minus_one(Ns, Bs), get_elems(Bs, As, Z).
Edit: The list of indices is guaranteed to be ascending, also I want to avoid implementing my own version of nth.
Give this a go:
get_elems(Xs,Ys,Zs) :- get_elems(Xs,1,Ys,Zs).
get_elems(Xs,_,Ys,[]) :- Xs = []; Ys = [].
get_elems([N|Xs],N,[H|Ys],[H|Zs]) :- !, N1 is N + 1, get_elems(Xs,N1,Ys,Zs).
get_elems(Xs,N,[_|Ys],Zs) :- N1 is N + 1, get_elems(Xs,N1,Ys,Zs).
This just keeps counting up and when the head of the second term is equal to the current index it peels off the head and makes it the head of the current output term. If it doesn't match it just discards the head and keeps going.

Storing results in a list in Prolog

I am trying to compute arithmetic calculations and store the results in a new list in Prolog.
The function prototype goes as follows:
calculation(List1, ListofLists, ResultList)
for the first argument I provide a list, for the second argument a list of lists and third the result list. I compute the first argument list with each list of list of lists and store the result in the resulting list.
So can somebody tell me how can I store results in the resulting (empty) list?
With library lambda you can write:
:- use_module(library(lambda)).
:- use_module(library(clpfd)).
calculation(L1, L2, Compute, L) :-
maplist([L2,Compute] +\X^Y^call(Compute,L2, X, Y), L1, L).
% my_compute succeeds when R is the list of all the products
% of the numbers component of L with the number V
my_compute(L, V, R) :-
maplist(V +\X^Y^maplist(V +\Z^T^(T #= Z * V), X, Y), L, R).
Here is an example:
?- calculation([1,2,3], [[4,5],[6,7]], my_compute, Zss).
Zss = [[[4, 5], [6, 7]], [[8, 10], [12, 14]], [[12, 15], [18, 21]]].
?- Zss = [[[4,5],[6,7]],[[8,10],[12,14]],[[12,15],[18,21]]],
calculation(Xs, [[4,5],[6,7]], my_compute, Zss).
Xs = [1, 2, 3].
?- Zss = [[[4,5],[6,7]],[[8,10],[12,14]],[[12,15],[18,21]]],
calculation([1,2,3], Xss, my_compute, Zss).
Xss = [[4, 5], [6, 7]].
calculation([], [], []).
calculation([X|Xs], [Y|Ys], [Z|Zs]) :-
calculate(X, Y, Z),
calculation(Xs, Ys, Zs).
which is identical to:
calculation(X, Y, Z) :-
maplist(calculate, X, Y, Z).
either way, you need a predicate calculate/3 that takes a first argument, a list of lists as the second argument, and calculates a result. For example, summing the list in the second argument and multiplying it to the first argument:
calculate(X, Ys, Z) :-
list_sum(Ys, S),
Z is X * S.
If I understood correctly, you want to do some computation on List1 and every member of ListofLists, and get a list of results.
You can do this using findall:
calculation(List1, ListofLists, ResultList) :-
findall(Result, (
member(List2, ListofLists),
your_computation(List1, List2, Result)
), ResultList).
For example, if you replace your_compuation with append, you get:
?- calculation([a,b],[[c,d],[e,f,g],[h]],X).
X = [[a, b, c, d], [a, b, e, f, g], [a, b, h]].

How to populate a list in Prolog?

Say you have the following predicate:
random_int(X/Y):-
random(1,100,X),
random(1,100,Y),
X\=Y.
How can I populate a list of size n using the result of this predicate?
I tried the following code but it only populates the list if random_int(X) is true at the first attempt, i.e. it does not backtrack to try other combinations of X and Y.
findall(X,(between(1,N,_), random_int(X)),L).
I find this small 'application' of clpfd interesting:
?- N=10,M=12, repeat, findall(X, (between(1,N,_),random(1,M,X)), L), clpfd:all_different(L).
N = 10,
M = 12,
L = [5, 4, 6, 7, 9, 11, 2, 3, 8|...]
.
note: M must be > N
I guess a simple way to do it is to make a list of 1:100, and draw 100 times from it a sample of size 2, without replacement. Since this is Prolog and not R, you can instead do:
:- use_module(library(lists)).
:- use_module(library(random)).
random_pairs(Pairs) :-
findall(X/Y,
( between(1, 100, _),
randseq(2, 100, [X,Y])
), R).
This is available in SWI-Prolog at least, but it is free software and the source to randseq/3 is available on the web site.
And since it's better to not use findall unless strictly necessary, it would probable better to write:
random_pairs(Pairs) :-
length(Pairs, 100),
maplist(randseq(2, 100), Pairs).
or, if the X/Y is important,
random_pairs(Pairs) :-
length(Pairs, 100),
maplist(rand_couple(100), Pairs).
rand_couple(N, X/Y) :-
randseq(2, N, [X,Y]).
TL;DR Use the available libraries
You could do it with findall/3:
random_list(N, L) :-
findall(X, (between(1,N,_), random(50,100,X)), L).
Another tidy way to do this would be:
random_list(N, L) :-
length(L, N),
maplist(random(50, 100), L).
Which results in:
| ?- random_list(5, L).
L = [69,89,89,95,59]
yes
| ?-
In general, if you have a predicate, p(X1,X2,...,Xn,Y), and a list you want to fill with result Y using successive calls to p/(n+1), you can use length(List, Length) to set the length of your list, and then maplist(p(X1,...,Xn), List) to populate the list. Or, using the findall/3, you can do findall(X, (between(1,N,_), p(X1,...,Xn,X)), L)..
EDIT based upon the updated conditions of the question that the generated list be unique values...
The random predicates are not generators, so they don't create new random numbers on backtracking (either unique or otherwise). So this solution, likewise, will generate one list which meets the requirements, and then just succeed without generating more such lists on backtracking:
% Generate a random number X between A and B which is not in L
rand_not_in(A, B, L, X) :-
random(A, B, X1),
( memberchk(X1, L)
-> rand_not_in(A, B, L, X)
; X = X1
).
% Generate a list L of length N consisting of unique random numbers
% between A and B
random_list(N, L) :-
random_list(N, 50, 100, [], L).
random_list(N, A, B, Acc, L) :-
N > 0,
rand_not_in(A, B, A, X),
N1 is N - 1,
random_list(N1, A, B, [X|A], L).
random_list(0, _, _, L, L).
Yet another approach, in SWI Prolog, you can use randseq, which will give a random sequence in a range 1 to N. Just scale it:
random_list(N, A, B, L) :-
A < B,
Count is B - A + 1,
randseq(N, Count, L1),
Offset is A - 1,
maplist(offset(Offset), L1, L).
offset(X, Offset, Y) :-
Y is X + Offset.
?- random_list(5, 50, 100, L).
L = [54, 91, 90, 78, 75].
?-
random_len([],0).
random_len([Q|T],N) :-
random(1,100,Q),
random_len(T,X),
N is X+1.

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