Impossible for me to solve: Simple recursion does not take integers for indexing a list....source_sink does not exist? - prolog

This recursion should slice IL to IR out of the list Lin and hand result LOut...
slice(_,IL,IR,LOut) :-
IR<IL,
[LOut].
slice(Lin,IL,IR,LOut) :-
nth0(IL,Lin,X),
append(LOut,[X],LOut2),
IK is IL + 1,
slice(Lin,IK,IR,LOut2).
Input / Output:
?- slice([1,2,3,4],2,3,X).
ERROR: source_sink `'3'' does not exist
ERROR: source_sink `'4'' does not exist
X = [] .
I m also new to Prolog, but I think this recursion must somehow work. Also I'm not really known to the error codes in Prolog, but after checking multiple times I just have to give up... I hope you guys can help me.

slice(_,IL,IR,LOut) :-
IR<IL,
[LOut]. % <-- this line causes source_sink error.
That syntax [name] tries to load the file name.pl as Prolog source code. By the time your code gets there, LOut is [3,4] so it tries to load the files 3.pl and 4.pl, and they don't exist (thankfully, or else who knows what they could do).
I think this recursion must somehow work
It won't; you are appending to a list as you go down into the recursion, which means you will never see the result.
The following might be a close version which works, at least one way:
slice(_,IL,IR,[]) :-
IR < IL.
slice(Lin,IL,IR,[X|LOut]) :-
IR >= IL,
nth0(IL,Lin,X),
IK is IL + 1,
slice(Lin,IK,IR,LOut).
?- slice([0,1,2,3,4,5,6,7,8,9], 2, 5, X).
X = [2, 3, 4, 5]
See how [X|LOut] in the second rule's header puts X in the result that you get, and append/3 is not needed, and LOut finishes down in the recursion eventually as [] the empty list from the first rule, and all the X's are prepended on the front of it to make the result on the way down into the recursion, which is tail recursion, so it doesn't need to go back up, only forward, since there's nothing left to be done after the recursive call.
Since the "cons" is done before the recursion, this is known as "tail recursion modulo cons" in other languages, but in Prolog it is just tail, and the list is being built top-down on the way forward, as opposed to being built bottom up on the way back:
Lin=[0,1,2,3,4,5,6,7,8,9], slice( Lin, 2, 5, R)
:-
nth0(2,Lin,X2), R=[X2|R2], slice( Lin, 3, 5, R2)
:-
nth0(3,Lin,X3), R2=[X3|R3], slice( Lin, 4, 5, R3)
:-
nth0(4,Lin,X4), R3=[X4|R4], slice( Lin, 5, 5, R4)
:-
nth0(5,Lin,X5), R4=[X5|R5], slice( Lin, 6, 5, R5)
:-
R5 = [].

I think findall/3 provides a readable readable solution for your problem:
slice(Lin,IL,IR,LOut) :-
findall(E,(nth0(P,Lin,E),between(IL,IR,P)),LOut).
yields
?- slice([1,2,3,4],2,3,X).
X = [3, 4].
If you expect a different outcome, use standard arithmetic comparison operators (=<,>=) instead of between/3.

I think you want:
list_elems_slice(Start, End, Lst, Slice) :-
list_elems_slice_(Lst, 1, Start, End, Slice).
list_elems_slice_([H|T], N, N, End, [H|Slice]) :-
list_elems_slice_capture_(T, N, End, Slice).
list_elems_slice_([_|T], N, Start, End, Slice) :-
N1 is N + 1,
list_elems_slice_(T, N1, Start, End, Slice).
list_elems_slice_capture_(_, N, N, []).
list_elems_slice_capture_([H|T], N, End, [H|Slice]) :-
N1 is N + 1,
list_elems_slice_capture_(T, N1, End, Slice).
Result in swi-prolog:
?- list_elems_slice(S, E, [a,b,c], Slice).
S = E, E = 1,
Slice = [a] ;
S = 1,
E = 2,
Slice = [a, b] ;
S = 1,
E = 3,
Slice = [a, b, c] ;
S = E, E = 2,
Slice = [b] ;
S = 2,
E = 3,
Slice = [b, c] ;
S = E, E = 3,
Slice = [c] ;
false.

Assuming that the point of this exercise is to teach you to think recursively, I would approach the problem as follows.
To get what you want is essentially two separate operations:
You first must discard some number of items from the beginning of the list, and then
Take some number of items from what's left over
That gives us discard/3:
discard( Xs , 0 , Xs ) .
discard( [_|Xs] , N , Ys ) :- N > 0 , N1 is N-1, discard(Xs,N1,Ys) .
and take/3, very nearly the same operation:
take( _ , 0 , [] ) .
take( [X|Xs] , N , [Y|Ys] ) :- N > 0 , N1 is N-1, take(Xs,N1,Ys) .
Once you have those two simple predicates, slice/4 itself is pretty trivial:
%
% slice( List , Left, Right, Sublist )
%
slice( Xs, L, R, Ys ) :- % to slice a list,
L =< R, % - the left offset must first be less than or equal to the right offset
N is R-L, % - compute the number of items required, and then
discard(Xs,L,X1), % - discard the first L items, and
take(X1,N,Ys). % - take the next N items
. % Easy!
Another approach would be to use append/3:
slice( Xs , L, R, Ys ) :-
length(Pfx,L), % - construct of list of the length to be discarded
append(Pfx,Sfx,Xs), % - use append to split Xs
N is R-L, % - compute the number of items required
length(Ys,N), % - ensure Ys is the required length
append(Ys,_,Sfx) % - use append to split off Ys
. % Easy!

Related

How to check how many elements you've already consumed in Prolog DCGs

Say I have these DCGs:
zorbs([H|T]) --> zorb(H), zorbs(T).
zorbs([]) --> [].
zorb(a) --> [1,2].
zorb(b) --> [3].
zorb(c) --> [6,1,2,2].
I can do this:
?- phrase(zorbs(X), [1,2,3,6,1,2,2]).
X = [a, b, c] .
I can also "reverse" this by doing:
phrase(zorbs([a,b,c]), X).
X = [1, 2, 3, 6, 1, 2, 2].
Now, what I want to do is find a list of numbers with length less than 4 (for example) which these elements "parse" into, returning the rest.
So, for example, given [a,b,c], which would normally relate to [1, 2, 3, 6, 1, 2, 2], I want it to relate to [1, 2, 3] (which has length less than 4) and also give the remainder that couldn't be "reversed," so [c]. I don't really know where to start, as it seems there's no way to reason about the number of elements you've already consumed in a DCG.
Here's a sort-of solution:
X in 0..4,
indomain(X),
Q = [_|_],
prefix(Q, [a,b,c]),
length(A, X),
phrase(zorbs(Q), A).
but I think this is very inefficient, because I think it basically iterates up from nothing, and I want to find the solution with the biggest Q.
There is no direct way how to do this in this case. So your approach is essentially what can be done. That is, you are enumerating all possible solutions and (what you have not shown) selecting them accordingly.
Questions about the biggest and the like include some quantification that you cannot express directly in first order logic.
However, sometimes you can use a couple of tricks.
Sometimes, a partial list like [a,b,c|_] may be helpful.
?- Xs = [_,_,_,_|_], phrase(zorbs(Xs),[1,2,3,6,1,2,2]).
false.
So here we have proven that there is no list of length 4 or longer that corresponds to that sequence. That is, we have proven this for infinitely many lists!
And sometimes, using phrase/3 in place of phrase/2 may help. Say, you have a number sequence that doesn't parse, and you want to know how far it can parse:
?- Ys0 = [1,2,3,6,1,2,7], phrase(zorbs(Xs),Ys0,Ys).
Ys0 = [1,2,3,6,1,2,7], Xs = [], Ys = [1,2,3,6,1,2,7]
; Ys0 = [1,2,3,6,1,2,7], Xs = "a", Ys = [3,6,1,2,7]
; Ys0 = [1,2,3,6,1,2,7], Xs = "ab", Ys = [6,1,2,7]
; false.
(This is with the two DCG-rules exchanged)
Can use:
% Like "between", but counts down instead of up
count_down(High, Low, N) :-
integer(High),
integer(Low),
count_down_(High, Low, N).
count_down_(H, L, N) :-
compare(C, H, L),
count_down_comp_(C, H, L, N).
count_down_comp_('=', _H, L, N) :-
% All equal, final
N = L.
% Accept H as the counting-down value
count_down_comp_('>', H, _L, H).
count_down_comp_('>', H, L, N) :-
H0 is H - 1,
% Decrement H towards L, and loop
count_down_(H0, L, N).
... and then start with:
count_down(4, 1, Len), length(Lst, Len), phrase...
Another method is to use freeze to limit a list's length, element-by-element:
max_len_freeze(Lst, MaxLen) :-
compare(C, MaxLen, 0),
max_len_freeze_comp_(C, Lst, MaxLen).
max_len_freeze_comp_('=', [], 0).
max_len_freeze_comp_('>', [_|Lst], MaxLen) :-
succ(MaxLen0, MaxLen),
!,
freeze(Lst, max_len_freeze(Lst, MaxLen0)).
max_len_freeze_comp_('>', [], _).
... and then start with:
max_len_freeze(Lst, 4), phrase...
This will work to find the longest list (maximum length 4) first, since your DCG is greedy (i.e. matching [H|T] before []).

using greedy algorithm search in lists

Given a list of positive integer Items whose elements are guaranteed to be in sorted ascending order, and a positive integer Goal, and Output is a list of three elements [A,B,C] taken from items that together add up to goal. The Output must occur inside the items list in that order (ascending order).
ex:
?- threeSum([3,8,9,10,12,14],27,Output).
Output=[8,9,10];
Output=[3,10,14].
someone helped me to reach this to this code
but it gives me singleton variables:[Input,Items] ,it didnt work
although iam not quite sure if this is a greedy algorithm search or not ?
threeSum(Input,Goal,[A,B,C]):-
permutation(Items, [A,B,C|Rest]),
msort([A,B,C],[A,B,C]),
msort(Rest,Rest),
sum_list([A,B,C],Goal).
A clpfd approach:
:- use_module(library(clpfd)).
threeSum(Input, Goal, [A,B,C]) :-
Input = [First|Rest],
foldl([N,M,T]>>(T = N\/M), Rest, First, Domain),
[A,B,C] ins Domain,
all_different([A,B,C]),
chain([A,B,C], #>=),
Goal #= A + B + C,
labeling([max(A), max(B), max(C)], [A,B,C]).
Which has a bit of wrangling to turn the list of numbers into a domain, then says [A,B,C] must be in the list of numbers, must be different numbers, must be in descending order, must sum to the goal, and the clpfd solver should strive to maximise the values of A then B then C. (This probably won't work if the list can contain multiple of the same value like [5,5,5,3,2]).
e.g.
?- threeSum([3,8,9,10,12,14], 27, Output).
Output = [14, 10, 3] ;
Output = [10, 9, 8]
nums_goal_answer(Input, Goal, [A,B,C]) :-
length(Input, InputLen),
reverse(Input, RInput), % 'greedy' interpreted as 'prefer larger values first'.
% and larger values are at the end.
between( 1, InputLen, N1),
between(N1, InputLen, N2), % three nested for-loops equivalent.
between(N2, InputLen, N3),
\+ N1 = N2, % can't pick the same thing more than once.
\+ N2 = N3,
nth1(N1, RInput, A, _),
nth1(N2, RInput, B, _),
nth1(N3, RInput, C, _),
sum_list([A,B,C], Goal).
someone helped me to reach this to this code but it gives me singleton variables:[Input,Items], it didnt work
The warning is because the code never looks at the numbers in the Input list. Without doing that, how could it ever work?
although iam not quite sure if this is a greedy algorithm
is it taking the biggest things first? I don't think permutation will do that.
Using DCG:
:- use_module(library(dcg/basics)).
three_sum_as_dcg(Total, Lst, LstThree) :-
phrase(three_sum_dcg(3, Total), Lst, LstThree).
% When finished, remove the remainder, rather than add to LstThree
three_sum_dcg(0, 0) --> remainder(_).
three_sum_dcg(NumsLeft, Total), [N] -->
% Use this element
[N],
{ three_sum_informed_search(NumsLeft, Total, N),
succ(NumsLeft0, NumsLeft),
Total0 is Total - N
},
three_sum_dcg(NumsLeft0, Total0).
three_sum_dcg(NumsLeft, Total) -->
% Skip this element
[N],
{ three_sum_informed_search(NumsLeft, Total, N) },
three_sum_dcg(NumsLeft, Total).
three_sum_informed_search(NumsLeft, Total, N) :-
NumsLeft > 0,
% "Informed" search calc due to list nums not decreasing
Total >= (N * NumsLeft).
Result in swi-prolog (note the efficiency):
?- numlist(1, 1000000, L), time(findall(L3, three_sum_as_dcg(12, L, L3), L3s)).
% 546 inferences, 0.000 CPU in 0.000 seconds (97% CPU, 4740036 Lips)
L3s = [[1,2,9],[1,3,8],[1,4,7],[1,5,6],[2,3,7],[2,4,6],[3,4,5]].
Restating the problem statement:
Given that I have
A [source] list of positive integers, whose elements are guaranteed to be sorted in ascending order, and
a positive integer indicating the target value.
I want to find
an ordered subset of elements of the source list that sum to the target value
The simplest way is often the easiest (and the most general):
sum_of( _ , 0 , [] ) . % nothing adds up to nothing.
sum_of( [X|Xs] , S , [X|Ys] ) :- % otherwise...
S > 0 , % - if the target sum S is positive,
X =< S , % - and the head of the list is less than or equal to the target sum
S1 is S-X , % - remove that amount from the target sum, and
sum_of(Xs,S1,Ys) . % - recurse down with the new target sum
sum_of( [_|Xs] , S , Ys ) :- % then, on backtracking...
S > 0 , % - assuming that the target sum is positive,
sum_of(Xs,S,Ys). % - recurse down again, discarding the head of the list
This will find whatever combinations of however many list elements sum to the target value. It will find them from left to right, so
sum_of( [1,2,3,4,5,6,7,8,9], 10, L ).
will, on backtracking successively find
L = [ 1, 2, 3, 4 ]
L = [ 1, 2, 7 ]
L = [ 1, 3, 6 ]
L = [ 1, 4, 5 ]
L = [ 1, 9 ]
L = [ 2, 3, 5 ]
L = [ 2, 8 ]
L = [ 3, 7 ]
L = [ 4, 6 ]
If you want to change the order so it finds the largest values first, simply reverse the order of clauses 2 and 3 in sum_of/3:
sum_of( _ , 0 , [] ) .
sum_of( [_|Xs] , S , Ys ) :-
S > 0 ,
sum_of(Xs,S,Ys) .
sum_of( [X|Xs] , S , [X|Ys] ) :-
S > 0 ,
X =< S ,
S1 is S-X ,
sum_of(Xs,S1,Ys) .
Now it will return the same set of solutions, just in the reverse order, starting with [4,6] and finishing with [1,2,3,4].
Once you have solved the general problem, it's a simple matter of restricting it to a specified number of elements, for instance:
sum_of_n_elements(Xs,N,S,Ys) :- length(Ys,N), sum_of(Xs,S,Ys).
And to get just the 3-element subsets that sum to the target value:
sum_of_3_elements(Xs,S,Ys) :- sum_of_n_elements(Xs,3,S,Ys) .
https://swish.swi-prolog.org/p/XKjdstla.pl

Prolog list exercise

Here is my exercise: define a predicate in prolog which, applied to a list L of integers, gives as a result the list of the successors of the even elements present in L.
The code i wrote work only if one element is even , can someone help me figure out where I'm wrong?
even(X):- 0 is mod(X,2).
odd(X):- 1 is mod(X,2).
list_even([],[]).
list_even([T|C],K):- even(T), E is T+1, list_even(C,K1), append(K1,E,X), K is X.
list_even([T|C],K):- odd(T),list_even(C,K).
Some flaws in your code are:
append(K1, E, X): This goal should append two lists to generate a third list; however, E is just an element, not a list. So you need to write append(K1, [E], X).
K is X: This goal evaluates the arithmetic expression represented by the variable X and unifies its value with variable K; however, X is a list, not an arithmetic expression. So you need to remove it.
So the correct code would be as follows:
list_even([], []).
list_even([T|C], K):- even(T), E is T+1, list_even(C, K1), append(K1, [E], K).
list_even([T|C], K):- odd(T), list_even(C, K).
Example:
?- list_even([1, 20, 3, 40, 5, 7, 8], Successors).
Successors = [9, 41, 21] ;
false.
Note that in the obtained answer, the successors appear in reverse order (the first even element in the input list is 20, but its successor 21 is the last element in the output list).
So a better code is as follows:
even_number_successors([], []).
even_number_successors([X|Xs], Successors) :-
( X mod 2 =:= 0
-> Y is X + 1,
Successors = [Y|Ys]
; Successors = Ys ),
even_number_successors(Xs, Ys).
Example:
?- even_number_successors([1, 20, 3, 40, 5, 7, 8], Successors).
Successors = [21, 41, 9].
From your problem statement,
define a predicate in prolog which, applied to a list L of integers, gives as a result the list of the successors of the even elements present in L.
On the face of things, you don't need odd/1: that which is not even is odd.
Why use append/3? You're just iterating/filtering a list and constructing a new one, right? Instead, you can construct the list in order by leaving the list incomplete, with an unbound tail. As we recurse down, we build out the tail of the list, either by unifying it with a new list, or at the end, unifying it with the empty list, the atom []).
I would do something like this:
list_even( [] , [] ) . % empty list? All done.
list_even( [X|Xs] , [Y|Ys] ) :- % non-empty?
even(X), % - is X even? if so...
!, % - eliminate the choice point
Y is X+1, % - get the successor of X
list_even(Xs,Ys) % - recurse down
. %
list_even( [_|Xs] , Ys ) :- % Otherwise, the head of the list is odd: discard the head, and...
list_even(Xs,Ys) % - recurse down
. % Easy!
even(X) :- 0 =:= X .

Prolog : Iterating over a list and creating a predicate

I'm creating a predicate enum that takes a list and a number for example [1,2,3,4] and 3 and returns a list that contains lists of length 3 made out of the list introduced. So in the example given enum([1,2,3,4],3,[[1,2,3],[2,3,4]]).
I've created a function take that takes only the first list of length N but I get errors when I try to loop it to get all of the others. Thanks you for helping.
append([],L,L).
append([H|T],L2,[H|L3]):- append(T,L2,L3).
len([],0).
len([_|B],X):- len(B,X1), X is X1+1.
take(_,X,Y) :- X =< 0, !, X =:= 0, Y = [].
take([],_,[]).
take([A|B],X,[A|C]):- Z is X-1, take(B,Z,C).
enum([],_,[]).
enum([N1|N2],N3,N4):-
len([N1|N2],U),
N3=<U,
take([N1|N2],N3,T1),
append([N4],[T1],T2),
!,
enum(N2,N3,T2).
I will focus on the take/3 predicate, which is the core of your question. In order to get a sublist like [2,3,4] of [1,2,3,4], you have to be able to skip the first element and just take a sublist of the rest.
You can achieve this by adding this clause to your definition:
take([_|Xs], N, Ys) :- take(Xs, N, Ys).
With this you now get several different sublists of length 3, but also some other superfluous solutions:
?- take([1,2,3,4], 3, Xs).
Xs = [1, 2, 3] ;
Xs = [1, 2, 4] ;
Xs = [1, 2] ;
Xs = [1, 3, 4] ;
Xs = [1, 3] ;
Xs = [1, 4] ;
Xs = [1] % etc.
This is because your clause take([], _, []) accepts an empty list as a "sublist of any length" of an empty list. I think you only wanted to accept the empty list as a sublist of length 0. If you remove this clause, your first clause will enforce that, and you only get solutions of length exactly 3:
?- take([1,2,3,4], 3, Xs).
Xs = [1, 2, 3] ;
Xs = [1, 2, 4] ;
Xs = [1, 3, 4] ;
Xs = [2, 3, 4] ;
false.
As a side note, your first clause is fine as is, but it can be simplified a bit to:
take(_,X,Y) :- X = 0, !, Y = [].
I would also advise you to use more readable variable names. For numbers like list lengths, we often use N. For lists, it's customary to use names like Xs, Ys, etc., with X, Y, etc. for members of the corresponding list.
Finally, to find all solutions of a predicate, you need to use a system predicate like setof, bagof, or findall. There is no way to write your enum in pure Prolog.
Because I am not sure about the advice in the other answer, here is my take on your problem.
First, don't define your own append/3 and length/2, append/3 is by now Prolog folklore, you can find it in textbooks 30 years old. And length/2 is really difficult to get right on your own, use the built-in.
Now: to take the first N elements at the front of a list L, you can say:
length(Front, N),
append(Front, _, L)
You create a list of the length you need, then use append/3 to split off this the front from the list you have.
With this in mind, it would be enough to define a predicate sliding_window/3:
sliding_window(L, N, [L]) :-
length(L, N).
sliding_window(L, N, [W|Ws]) :-
W = [_|_], % W should be at least one long
length(W, N),
append(W, _, L),
L = [_|L0],
sliding_window(L0, N, Ws).
This kind of works, but it will loop after giving you all useful answers:
?- sliding_window([a,b], N, Ws).
N = 2,
Ws = [[a, b]] ;
N = 1,
Ws = [[a], [b]] ;
% loops
It loops because of the same little snippet:
length(Front, N),
append(Front, _, L)
With length/2, you keep on generating lists of increasing length; once Front is longer than L, the append/3 fails, length/2 makes an even longer list, and so on forever.
One way out of this would be to use between/3 to constrain the length of the front. If you put it in its own predicate:
front_n(L, N, F) :-
length(L, Max),
between(1, Max, N),
length(F, N),
append(F, _, L).
With this:
sliding_window(L, N, [L]) :-
length(L, N).
sliding_window(L, N, [W|Ws]) :-
front_n(L, N, W),
L = [_|L0],
sliding_window(L0, N, Ws).
And now it finally works:
?- sliding_window([a,b,c,d], 3, Ws).
Ws = [[a, b, c], [b, c, d]] ;
false.
?- sliding_window([a,b,c], N, Ws).
N = 3,
Ws = [[a, b, c]] ;
N = 1,
Ws = [[a], [b], [c]] ;
N = 2,
Ws = [[a, b], [b, c]] ;
false.
Exercise: get rid of the harmless, but unnecessary choice point.

Prolog does not end calculation?

This is rather a technical question I think, I am trying to write a program that will find me all sub-sets of size K of the integers 1,2,...,N.
In here I've asked about a sub-set function that I'm using. The fixed version is:
subs(0,[],X).
subs(N,[A|R1],[A|R2]):-
N>0,
N1 is N-1,
subs(N1,R1,R2).
subs(N,[A|R1],[B|R2]):-
N>0,
subs(N,[A|R1],R2).
Later I wrote two functions to help me find the last element in a set and the sub-set of all element except the last (because [A|Rest] means A is the first and Rest is from number 2 to last, but I'd like the opposite - having the last elements and all the elements from the first to the one before the last). The functions are:
lastOf(A,[A]).
lastOf(A,[B|R]):-
lastOf(A,R).
subLast([],[X]).
subLast([A|R1],[A|R2]):-
subLast(R1,R2).
Now I wrote a function that creates a list of the first N natural numbers:
setOf(0,[]).
setOf(N,Nums):-
lastOf(N,Nums),
N>0, N1 is N-1,
subLast(NeoNums,Nums),
setOf(N1, NeoNums).
To combine all the above I have:
choose(K,N,X):-
setOf(N,Y),
subs(K,X,Y).
Running it, for example on 2 and 4, I get:
?-choose(2,4,X).
X = [1, 2] ;
X = [1, 3] ;
X = [1, 4] ;
X = [2, 3] ;
X = [2, 4] ;
X = [3, 4] ;
abort
% Execution Aborted
14 ?- ERROR: Stream user_input:6:143 Syntax error: Unexpected end of clause
These are all the correct outputs, but the problem is that after every time I press enter for a (possible) next answer, I get the next one, apart from the last, in which I have to forcefully abort, as it seems like the programs gets stuck in an infinite loop of some sort.
Can anyone assist?
I'm using SWI-Prolog.
If you're using SWI-Prolog, you can also use clpfd! Here's a clpfd variant of choose/3:
:- use_module(library(clpfd)).
choose(K,N,Zs) :-
length(Zs,K),
Zs ins 1..N,
chain(Zs,#<),
labeling([],Zs).
That's it! And here's the query you gave in the question:
?- choose(2,4,Zs).
Zs = [1,2] ;
Zs = [1,3] ;
Zs = [1,4] ;
Zs = [2,3] ;
Zs = [2,4] ;
Zs = [3,4]. % the goal `choose(2,4,Zs)` terminates
The setOf is the problem here. More specifically - lastOf, which is generating an infinite number of possible lists ending with N. Anyway, setOf can be implemented much easier and in much more readable way (and which is terminating):
setOf(0, []).
setOf(N, [N|T]) :-
N > 0,
N1 is N-1,
setOf(N1, T).
This is if you don't care about the reverse order of the numbers. Otherwise by introducing a helper predicate:
setOf(N, X) :- range(1, N, X).
% range(LowerBound, UpperBound, ResultList)
range(L, L, [L]).
range(L, U, [L|T]) :-
L < U,
L1 is L + 1,
range(L1, U, T).

Resources