How to create a infinite list if input is not delcared? - prolog

I have a written a functional function that tells the user if a list is ordered or not, given the list inputted. However, if a user inputs a variable as the input instead of a list, I would like to output an infinite list. How can I go about this? Here is the current code
ordered([]).
ordered([_]).
ordered([X,Y|Ys]) :- X =< Y , ordered( [Y|Ys] ).
Here is some input
? ordered([1,2,3]).
true
? ordered([1,5,2]).
false
I also want for variables to creat infinite list like so
? ordered(L).
L = [];
L = [_1322] ;
L = [_1322, _1323] ;
L = [_1322, _1323, _1324] ;
L = [_1322, _1323, _1324, _1325].
The list should increase until the user exits as shown.

The list should increase until the user exits as shown.
Solution:
ordered([]).
ordered([_]).
ordered([X,Y|Ys]) :- X #=< Y , ordered( [Y|Ys] ).
EDIT:
SWI Prolog doc
The arithmetic expression X is less than or equal to Y. When reasoning over integers, replace (=<)/2 by #=</2 to obtain more general relations. See declarative integer arithmetic (section A.9.3).

What properties should the list of variables have? The currently accepted answer by Anton Danilov says that [3, 2, 1] is not an ordered list:
?- List = [A, B, C], List = [3, 2, 1], ordered(List).
false.
but it also says that [3, 2, 1] is an instance of an ordered list:
?- List = [A, B, C], ordered(List), List = [3, 2, 1].
List = [3, 2, 1],
A = 3,
B = 2,
C = 1 ;
false.
Viewed logically, this is a contradiction. Viewed procedurally, it is fine, but also the #=< relationship between the variables in the list is meaningless. The comparison of the unbound variables does not say anything about the relationship of the list elements if they are bound to values at some point.
You can use constraints to exclude future unordered bindings:
:- use_module(library(clpfd)).
ordered([]).
ordered([_]).
ordered([X, Y | Xs]) :-
X #=< Y,
ordered([Y | Xs]).
This way you cannot bind the variables in the list to incorrect numbers later on:
?- List = [A, B, C], List = [3, 2, 1], ordered(List).
false.
?- List = [A, B, C], ordered(List), List = [3, 2, 1].
false.
But later correct ordered bindings are still allowed:
?- List = [A, B, C], ordered(List), List = [1, 2, 3].
List = [1, 2, 3],
A = 1,
B = 2,
C = 3 ;
false.

This may not be the best solution, but I believe it can give you some idea of how to do what you need. In SWI-Prolog, the predicate freeze(+Var,:Goal) delays the execution of Goal until Var is bound.
ordered([]).
ordered([_]).
ordered([X,Y|R]) :-
freeze( X,
freeze( Y,
( X #=< Y,
ordered([Y|R]) ) ) ).
Here are some examples with finite lists:
?- ordered([1,2,3]).
true.
?- ordered([1,2,3,0]).
false.
?- ordered(L), L=[1,2,3].
L = [1, 2, 3] ;
false.
?- ordered(L), L=[1,2,3,0].
false.
For an infinite list, you will need to "take" its prefix:
take([]).
take([_|R]) :- take(R).
Here is an example with infinite list:
?- ordered(L), take(L).
L = [] ;
L = [_375396] ;
L = [_376366, _376372],
freeze(_376366, freeze(_376372, (_376366#=<_376372, ordered([])))) ;
L = [_377472, _377478, _377484],
freeze(_377472, freeze(_377478, (_377472#=<_377478, ordered([_377484])))) ;
L = [_378590, _378596, _378602, _378608],
freeze(_378590, freeze(_378596, (_378590#=<_378596, ordered([_378602, _378608])))) ;
L = [_379720, _379726, _379732, _379738, _379744],
freeze(_379720, freeze(_379726, (_379720#=<_379726, ordered([_379732, _379738, _379744]))))

Related

Prolog check if list X has any duplicates

I have the function already but it is not working exactly as I want it to. The function I have is below..
isSet(List) :-
\+ (
select(Element, List, Tail),
select(Element, Tail, _)
).
When I do isSet([1,2,3]) it gives me true which is expected. When I do isSet([1,1,2]) it gives me false which is also what I expect and is correct. My question is how can I pass a list that is already made? For example If I do X = [1,2,3] and than pass it as a argument like isSet(X) it should give me true but instead it generates an error.
What can I do to fix this?
Edit:
?- [db].
true.
?- X = [1,2,3].
X = [1, 2, 3].
?- isSet(X).
false.
?- X = (1,2,3).
X = (1, 2, 3).
?- isSet(X).
false.
?- X = [1,1,2].
X = [1, 1, 2].
?- isSet(X).
false.
SWI-Prolog allows the form $Xs to access a variable from a previous query. E.g.:
?- Xs=[1,2,3].
Xs = [1, 2, 3].
?- isSet($Xs).
Xs = [1, 2, 3].
?- isSet([1|$Xs]).
false.
BTW, it's slightly more efficient to write your code like this (and I suggest using Rest rather than Tail: the latter is typically used in the form List=[Head|Tail]):
isSet(List) :-
\+ ( select(Element, List, Rest),
member(Element, Rest)
).
Also, you can't write a list like this: X = (1,2,3) ... that's actually something different:
?- write_canonical((1,2,3)), nl.
','(1,','(2,3))
true.
As there are discussions on how to best define the concept of "sets represented by lists", I humbly submit the following:
real_actual_set([]).
real_actual_set([X | Xs]) :-
nonmember_of(X, Xs),
real_actual_set(Xs).
nonmember_of(_X, []).
nonmember_of(X, [Y | Ys]) :-
dif(X, Y),
nonmember_of(X, Ys).
This is pure and works properly even in the presence of variables, including the most general query, and any lists containing variables that we would try to bind later:
?- real_actual_set([1, 2, 3]).
true .
?- real_actual_set([1, 1, 2]).
false.
?- real_actual_set([A, B, C]).
dif(A, C),
dif(A, B),
dif(B, C).
?- real_actual_set([A, A, B]).
false.
?- real_actual_set(Set).
Set = [] ;
Set = [_2222] ;
Set = [_2672, _2678],
dif(_2672, _2678) ;
Set = [_2970, _2976, _2982],
dif(_2970, _2982),
dif(_2970, _2976),
dif(_2976, _2982) ;
Set = [_3388, _3394, _3400, _3406],
dif(_3388, _3406),
dif(_3388, _3400),
dif(_3388, _3394),
dif(_3400, _3406),
dif(_3394, _3400),
dif(_3394, _3406) .
?- real_actual_set([A, B, C]), A = 1, B = 2, C = 3.
A = 1,
B = 2,
C = 3.
?- real_actual_set([A, B, C]), A = 1, B = 1, C = 3.
false.
This is quadratic, so it's "less performant" than other approaches. But as John Ousterhout is quoted, "The best performance improvement is the transition from the nonworking state to the working state."
The correct way to check if a list is a set in Prolog is to sort it, removing duplicates, and check if its length is still the same. This is correct for all kinds of reasons, from very pragmatic (easy to program) to purely theoretic (it is the only robust approach to checking if a singly linked list is a set).
"But this is not what I asked" sure it isn't.
is_set(List) :-
sort(List, Sorted),
length(List, N),
length(Sorted, N).
Don't throw Bloom filters and the like at me, at least not without proper justification.
To address the comments by #IsabelleNewbie, if you really want to use attributed variables to make sure that a list will forever remain a set under unification, you would do:
all_different([]).
all_different([H|T]) :-
maplist(dif(H), T),
all_different(T).
but this is a different thing altogether. You also shouldn't use it unless you want to take a list with variables and make sure no two elements in this list will ever unify. You get answers like this (in SWI-Prolog):
?- all_different(X).
X = [] ;
X = [_] ;
X = [_A, _B],
dif(_A, _B) ;
X = [_A, _B, _C],
dif(_A, _B),
dif(_A, _C),
dif(_B, _C) ;
X = [_A, _B, _C, _D],
dif(_A, _B),
dif(_A, _D),
dif(_A, _C),
dif(_B, _D),
dif(_B, _C),
dif(_C, _D) .
I suspect you can find this code in other places too.
For example If I do X = [1,2,3] and than pass it as a argument like isSet(X) it should give me true but instead it generates an error.
You should show us exactly what you tried!
This works:
?- Xs = [1, 2, 3], isSet(Xs).
Xs = [1, 2, 3].
Note that both parts (binding Xs and testing it) are in one query. Maybe you tried entering them separately:
?- Xs = [1, 2, 3].
Xs = [1, 2, 3].
?- isSet(Xs).
false.
This doesn't work because the value of Xs is not saved from one query to the next. This still isn't an error, though. However, it is not great behavior because failing for isSet(Xs) seems to imply that no sets exist at all.

How can I substract in prolog the elements from this structure: s(1, [[],[],[],[]] )? I need the integer and the matrix

I am quite new in prolog and I've met this structure and I could not figure out how to substact the integer (1) and the matrix.
The exact structure is:
s(1,
[
[[a], [b, c], [f], [s]],
[[4], [k], [1], [5]],
[[f], [s], [w], []],
[[4], [], [w], [3, 53]]
]
)
I've tried with functions that extract elements of lists/matrices, but I haven't met anything in () before.
My guess is you have a variable with the content s(Integer, Matrix) and want to extract the Integer and Matrix. This is actually quite easy:
Lets go with a dummy object S = s(3, [[[1,2],[a,b]]]). You only have S and want to access 3 and [[[1,2],[a,b]]]
?- S = s(3, [[[1,2],[a,b]]]),
S = s(I,M).
I = 3,
M = [[[1, 2], [a, b]]],
S = s(3, [[[1, 2], [a, b]]])
You can put this in some kind of function too. The following example will output an addtion if the predicate name is a, a substraction for s and or h it will put the first parameter as head of a list of the second parameter:
doIt(a(A,B),Out) :-
Out is A+B.
doIt(s(A,B),Out) :-
Out is A-B.
doIt(h(A,B),[A|B]).
?- doIt(a(2,1),A).
A = 3
?- doIt(s(2,1),A).
A = 1
?- doIt(h(2,1),A).
A = [2|1]

Calculate whether the sum of exactly three values in a list is equal to N

Examples: ([1,2,3,7,6,9], 6). should print True, as 1+2+3=6.
([1,2,3,7,6,9], 5). should print False as there are no three numbers whose sum is 5.
([],N) where N is equal to anything should be false.
Need to use only these constructs:
A single clause must be defined (no more than one clause is allowed).
Only the following is permitted:
+, ,, ;, ., !, :-, is, Lists -- Head and Tail syntax for list types, Variables.
I have done a basic coding as per my understanding.
findVal([Q|X],A) :-
[W|X1]=X,
[Y|X2]=X,
% Trying to append the values.
append([Q],X1,X2),
% finding sum.
RES is Q+W+Y,
% verify here.
(not(RES=A)->
% finding the values.
(findVal(X2,A=)->
true
;
(findVal(X,A)->
% return result.
true
;
% return value.
false))
;
% return result.
true
).
It does not seem to run throwing the following error.
ERROR:
Undefined procedure: findVal/2 (DWIM could not correct goal)
Can someone help with this?
You can make use of append/3 [swi-doc] here to pick an element from a list, and get access to the rest of the elements (the elements after that element). By applying this technique three times, we thus obtain three items from the list. We can then match the sum of these elements:
sublist(L1, S) :-
append(_, [S1|L2], L1),
append(_, [S2|L3], L2),
append(_, [S3|_], L3),
S is S1 + S2 + S3.
Well, you can iterate (via backtracking) over all the sublists of 3 elements from the input list and see which ones sum 3:
sublist([], []).
sublist([H|T], [H|S]) :- sublist(T, S).
sublist([_|T], S) :- sublist(T, S).
:- length(L, 3), sublist([1,2,3,7,6,9], L), sum_list(L, 6).
I'm giving a partial solution here because it is an interesting problem even though the constraints are ridiculous.
First, I want something like select/3, except that will give me the tail of the list rather than the list without the item:
select_from(X, [X|R], R).
select_from(X, [_|T], R) :- select_from(X, T, R).
I want the tail, rather than just member/2, so I can recursively ask for items from the list without getting duplicates.
?- select_from(X, [1,2,3,4,5], R).
X = 1,
R = [2, 3, 4, 5] ;
X = 2,
R = [3, 4, 5] ;
X = 3,
R = [4, 5] ;
X = 4,
R = [5] ;
X = 5,
R = [] ;
false.
Yeah, this is good. Now I want to build a thing to give me N elements from a list. Again, I want combinations, because I don't want unnecessary duplicates if I can avoid it:
select_n_from(1, L, [X]) :- select_from(X, L, _).
select_n_from(N, L, [X|R]) :-
N > 1,
succ(N0, N),
select_from(X, L, Next),
select_n_from(N0, Next, R).
So the idea here is simple. If N = 1, then just do select_from/3 and give me a singleton list. If N > 1, then get one item using select_from/3 and then recur with N-1. This should give me all the possible combinations of items from this list, without giving me a bunch of repetitions I don't care about because addition is commutative and associative:
?- select_n_from(3, [1,2,3,4,5], R).
R = [1, 2, 3] ;
R = [1, 2, 4] ;
R = [1, 2, 5] ;
R = [1, 3, 4] ;
R = [1, 3, 5] ;
R = [1, 4, 5] ;
R = [2, 3, 4] ;
R = [2, 3, 5] ;
R = [2, 4, 5] ;
R = [3, 4, 5] ;
false.
We're basically one step away now from the result, which is this:
sublist(List, N) :-
select_n_from(3, List, R),
sumlist(R, N).
I'm hardcoding 3 here because of your problem, but I wanted a general solution. Using it:
?- sublist([1,2,3,4,5], N).
N = 6 ;
N = 7 ;
N = 8 ;
N = 8 ;
N = 9 ;
N = 10 ;
N = 9 ;
N = 10 ;
N = 11 ;
N = 12 ;
false.
You can also check:
?- sublist([1,2,3,4,5], 6).
true ;
false.
?- sublist([1,2,3,4,5], 5).
false.
?- sublist([1,2,3,4,5], 8).
true ;
true ;
false.
New users of Prolog will be annoyed that you get multiple answers here, but knowing that there are multiple ways to get 8 is probably interesting.

SWI-Prolog Delete items that have pair occurrences

I need a solution that deletes elements that have pairs of occurrences from list.
I did it in haskell, but i don't have any ideas how to interpretate it in Prolog.
For example [1,2,2,2,4,4,5,6,6,6,6] -> [1,2,2,2,5]
Code in Haskell :
import Data.List
count e list = length $ filter (==e) list
isnotEven = (== 1) . (`mod` 2)
removeUnique :: [Int] -> [Int]
removeUnique list = filter (\x -> isnotEven (count x list) ) list
The following follows your Haskell code.
You need library(reif) for SICStus|SWI.
:- use_module(reif).
oddcount_t(List, E, T) :- % reified: last argument is truth value
tfilter(=(E), List, Eqs),
length(Eqs, Nr),
M is Nr mod 2,
=(M, 1, T).
removeevenocc(List, RList) :-
tfilter(oddcount_t(List), List, RList).
?- removeevenocc([1,2,2,2,4,4,5,6,6,6,6], R).
R = [1,2,2,2,5].
?- removeevenocc([1,X], R).
X = 1, R = []
; R = [1, X],
dif(X, 1).
Note the last question. Here, the list was not entirely given: The second element is left unknown. Therefore, Prolog produces answers for all possible values of X! Either X is 1, then the resulting list is empty, or X is not 1, then the list remains the same.
this snippet uses some of the libraries (aggregate,lists,yall) available, as well as some builtins, like setof/3, and (=:=)/2:
?- L=[1,2,2,2,4,4,5,6,6,6,6],
| setof(K,C^(aggregate(count,member(K,L),C),0=:=C mod 2),Ds),
| foldl([E,X,Y]>>delete(X,E,Y),Ds,L,R).
L = [1, 2, 2, 2, 4, 4, 5, 6, 6|...],
Ds = [4, 6],
R = [1, 2, 2, 2, 5].
edit
to account for setof/3 behaviour (my bug: setof/3 fails if there are no solutions), a possible correction:
?- L=[1],
(setof(K,C^(aggregate(count,member(K,L),C),0=:=C mod 2),Ds);Ds=[]),
foldl([E,X,Y]>>delete(X,E,Y),Ds,L,R).
L = R, R = [1],
Ds = [].
Now there is a choice point left, the correct syntax could be
?- L=[1],
(setof(K,C^(aggregate(count,member(K,L),C),0=:=C mod 2),Ds)->true;Ds=[]),
foldl([E,X,Y]>>delete(X,E,Y),Ds,L,R).
L = R, R = [1],
Ds = [].

ERROR: Out of global stack with append/3

I have a problem. I want to implement a replace(E1, L1, E2, L2) predicate.
This holds when L1 and L2 are the same lists,except that in one place where L1 has the value E1, L2 has E2. In addition, only one occurrence is replaced and it must work in any mode.
For example:
replace(2,[1,2,3,4],5,X) should have only the solution X = [1,5,3,4].
replace(2,[1,2,3,2,1],5,X) should backtrack over the solutions X =
[1,5,3,2,1] and X = [1,2,3,5,1].
replace(2,X,5,[1,5,3,5,1]) should backtrack over the solutions X =
[1,2,3,5,1] and X = [1,5,3,2,1].
replace(X,[a,b,c,d],Y,[a,e,c,d]) should have only the solution X = b,
Y = e.
replace(X,[1,2,3,2,1],Y,[1,5,3,5,1]) should have no solutions (it
should fail).
My implementation:
replace(E1, L1, E2, L2) :-
append(X, [E1|L_Tail], L1),
append(X, [E2|L_Tail], L2).
This code is fine. However when replace(2,X,5,[1,5,3,5,1]), it should return X = [1,2,3,5,1] and X = [1,5,3,2,1] and false. It only return the first 2 results, and the false didn't came up. The program end up with ERROR: Out of global stack.
This question has been asked and it has two answers: the one you used and a better one. However, I will answer the question "why does this solution not work and how to fix it?".
When the third argument to append/3 is a variable or a partial list, it gives infinitely many solutions:
?- append(X, Y, [a|Z]).
X = [],
Y = [a|Z] ;
X = [a],
Y = Z ;
X = [a, _1860],
Z = [_1860|Y] ;
X = [a, _1860, _1872],
Z = [_1860, _1872|Y] ;
X = [a, _1860, _1872, _1884],
Z = [_1860, _1872, _1884|Y] . % and so on
So, when the first list L1 is a partial list, the call to append(X, [E1|Y], L1) will keep "hallucinating" longer and longer lists. The second call to append/3 will fail every time, Prolog will backtrack, make an even longer list with the first append/3, and so on. This is why you are caught in an infinite loop and will eventually run out of memory (when the lists get too long).
One cheap way to avoid this is to make sure that both lists are proper lists of the same length before giving them to the two appends. For example:
same_length([], []).
same_length([_|A], [_|B]) :- same_length(A, B).
If you are using SWI-Prolog you could do this with maplist and a yall lambda:
maplist([_,_]>>true, L1, L2)
The example query:
?- L2 = [1,5,3,5,1],
maplist([_,_]>>true, L1, L2),
append(X, [2|Y], L1),
append(X, [5|Y], L2).
L2 = [1, 5, 3, 5, 1],
L1 = [1, 2, 3, 5, 1],
X = [1],
Y = [3, 5, 1] ;
L2 = [1, 5, 3, 5, 1],
L1 = [1, 5, 3, 2, 1],
X = [1, 5, 3],
Y = [1] ;
false.

Resources