Remove leading zeros in list in Prolog - list

I have a list with an unknown number of zeros at the beginning of it, for example [0, 0, 0, 1, 2, 0, 3]. I need this list to be stripped of leading zeros, so that it would look like [1, 2, 0 , 3].
Here's what I have:
lead([Head | _], _) :- Head =\= 0.
lead([0 | Tail], _) :-
lead(Tail, Tail).
The output of which is simply True. Reading the trace shows that it is running until it has a list with no leading zeros, but then the answer doesn't propagate back up the stack. I'm pretty new to Prolog, so I can't figure out how to make it do that.

Here is a solution that works in all directions:
lead([],[]).
lead([H|T],[H|T]) :-
dif(H,0).
lead([0|T],T2) :-
lead(T,T2).
Some queries:
?- lead([0,0,0,1,2,0,3], L).
L = [1, 2, 0, 3] ;
false.
?- lead(L, []).
L = [] ;
L = [0] ;
L = [0, 0] ;
L = [0, 0, 0] ;
...
?- lead(L0, L).
L0 = L, L = [] ;
L0 = L, L = [_G489|_G490],
dif(_G489, 0) ;
L0 = [0],
L = [] ;
L0 = [0, _G495|_G496],
L = [_G495|_G496],
dif(_G495, 0) ;
L0 = [0, 0],
L = [] ;
L0 = [0, 0, _G501|_G502],
L = [_G501|_G502],
dif(_G501, 0) ;
L0 = [0, 0, 0],
L = [] ;
...
EDIT This predicate actually doesn't work for e.g. lead(L0, [0,1,2]).

With library(reif):
:- use_module(reif).
remove_leading_zeros([], []).
remove_leading_zeros([H|T], Rest) :-
if_( H = 0,
remove_leading_zeros(T, Rest),
Rest = [H|T]).
Then:
?- remove_leading_zeros([0,0,0,1,2,0,3], R).
R = [1, 2, 0, 3].
?- remove_leading_zeros([2,0,3], R).
R = [2, 0, 3].
?- remove_leading_zeros(L, R).
L = R, R = [] ;
L = [0],
R = [] ;
L = [0, 0],
R = [] ;
L = [0, 0, 0],
R = [] . % and so on

Here is a solution that actually works for all possible inputs and doesn't leave unnecessary choice points:
lead(L0, L) :-
( nonvar(L),
L = [H|_] ->
dif(H,0)
;
true
),
lead_(L0, L).
lead_([], []).
lead_([H|T], L) :-
if_(H \= 0,
L = [H|T],
lead_(T,L)).
The initial check for nonvar(L) is the only solution I have been able to come up with that would prevent problems with e.g. lead(L0, [0,1,2,3]), while retaining the behavior of the predicate in all other situations.
This uses if_/3, part of library(reif)
if_(If_1, Then_0, Else_0) :-
call(If_1, T),
( T == true -> Then_0
; T == false -> Else_0
; nonvar(T) -> throw(error(type_error(boolean,T),
type_error(call(If_1,T),2,boolean,T)))
; throw(error(instantiation_error,instantiation_error(call(If_1,T),2)))
).
This also uses (\=)/3, that I came up with by simple modification of (=)/3 in library(reif).
\=(X, Y, T) :-
( X \= Y -> T = true
; X == Y -> T = false
; T = true, dif(X, Y)
; T = false,
X = Y
).
Some queries
?- lead([0,0,0,1,2,0,3],L). % No choice point
L = [1, 2, 0, 3].
?- lead([1,2,0,3],L).
L = [1, 2, 0, 3].
?- lead([0,0,0,0],L).
L = [].
?- lead([],L).
L = [].
?- lead(L0,[0,1,2,0,3]). % Correctly fails
false.
?- lead(L0,[1,2,0,3]).
L0 = [1, 2, 0, 3] ;
L0 = [0, 1, 2, 0, 3] ;
L0 = [0, 0, 1, 2, 0, 3] ;
…
?- lead(L0,L). % Exhaustively enumerates all cases:
L0 = L, L = [] ; % - LO empty
L0 = L, L = [_G2611|_G2612], % - L0 contains no leading 0
dif(_G2611, 0) ;
L0 = [0], % - L0 = [0]
L = [] ;
L0 = [0, _G2629|_G2630], % - L0 contains one leading 0
L = [_G2629|_G2630],
dif(_G2629, 0) ;
L0 = [0, 0], % - L0 = [0, 0]
L = [] ;
L0 = [0, 0, _G2647|_G2648], % - L0 contains two leading 0s
L = [_G2647|_G2648],
dif(_G2647, 0) ;
… % etc.

Here is a solution that doesn't generate any choice points. Its
using freeze/2, in a way that is not anticipated by dif/2. But using
freeze/2 here is quite appropriate, since one rule of thumb for freeze/2
is as follows:
Rule of Thumb for freeze/2: Use freeze/2 where the predicate would
generate uninstantiated solutions and a lot of choice points. The hope
is that a subsequent goal will specify the solution more, and the
freeze/2 will be woken up. Unfortunately doesn't work with CLP(FD) or
dif/2, since freeze/2 does not react to refinements implied by CLP(FD)
or dif/2, only unification will wake it up.
The code is thus:
lead(X, Y) :- var(X), !, freeze(X, lead(X,Y)).
lead([X|Y], Z) :- var(X), !, freeze(X, lead([X|Y],Z)).
lead([0|X], Y) :- !, lead(X, Y).
lead(X, X).
Here are some sample runs (SWI-Prolog without some import, Jekejeke Prolog use Minlog Extension and ?- use_module(library(term/suspend))):
?- lead([0,0,0,1,2,3], X).
X = [1, 2, 3].
?- lead([0,0|X], Y).
freeze(X, lead(X, Y)).
?- lead([0,0|X], Y), X = [0,1,2,3].
X = [0, 1, 2, 3],
Y = [1, 2, 3].
?- lead([Z,0|X], Y), X = [0,1,2,3].
X = [0, 1, 2, 3],
freeze(Z, lead([Z, 0, 0, 1, 2, 3], Y)).
?- lead([Z,0|X], Y), X = [0,1,2,3], Z = 0.
Z = 0,
X = [0, 1, 2, 3],
Y = [1, 2, 3].
In the above lead/2 implemetation only the first argument is handled. To handle multiple arguments simultaneously the predicate when/2 can be used. But for simplicity this is not shown here.
Also when using suspended goals, one might need a labeling like predicate at the end, since suspended goals cannot detect inconsistency among them.

The problem in your code is that the second parameter, your output, is specified as _, so your predicate is true for any output. What you want is a predicate that is true if and only if it is the input minus leading zeroes.
lead([], []).
lead([0 | Tail], Tail2) :- !, lead(Tail, Tail2).
lead([Head | Tail], [Head | Tail]) :- Head =\= 0.
The ! in the first line is optional. It prunes the search tree so Prolog does not consider the second line (which would fail) if the first line matches.

Here's how I'd phrase it. First, establish constraints: either X or Y must be bound to a list. Anything else fails.
If X is bound, we don't care about Y: it can be bound or unbound. We just strip any leading zeros from X and unify the results with Y. This path has a single possible solution.
If X is unbound and Y is bound, we shift into generative mode. This path has an infinite number of possible solutions.
The code:
strip_leading_zeros(X,Y) :- listish(X), !, rmv0( X , Y ) .
strip_leading_zeros(X,Y) :- listish(Y), !, add0( Y , X ) .
rmv0( [] , [] ) .
rmv0( [D|Ds] , R ) :- D \= 0 -> R = [D|Ds] ; rmv0(Ds,R) .
add0( X , X ) .
add0( X , Y ) :- add0([0|X],Y ) .
listish/1 is a simple shallow test for listish-ness. Use is_list/1 if you want to be pedantic about things.
listish( L ) :- var(L), !, fail.
listish( [] ) .
listish( [_|_] ) .
Edited to note: is_list/1 traverses the entire list to ensure that it is testing is a properly constructed list, that is, a ./2 term, whose right-hand child is itself either another ./2 term or the atom [] (which denotes the empty list). If the list is long, this can be an expensive operation.
So, something like [a,b,c] is a proper list and is actually this term: .(a,.(b,.(c,[]))). Something like [a,b|32] is not a proper list: it is the term .(a,.(b,32)).

Related

Prolog Compare elements of list

When given some input list, I want to build a new list and it should:
Always add h in front of the new list
Compare every two consecutive elements of the input list, and, if they are
equal, append y to the new list, if not, append x.
Example:
?- control([a,a,b,b],R).
R = [h,y,x,y].
Here is my code so far:
control([H,H|T],K,[K,0|T2]):- control([H|T],[K,0],T2).
control([H,J|T],K,[K,1|T2]):- control([J|T],[K,1],T2).
control([H],G,G).
But it is not working correctly.
?- control([a,a,b,b],[h],L).
L = [[h], 0, [[h], 0], 1, [[[h], 0], 1], 0, [[[...]|...], 1], 0] ;
L = [[h], 0, [[h], 0], 1, [[[h], 0], 1], 1, [[[...]|...], 1], 1] ;
L = [[h], 1, [[h], 1], 1, [[[h], 1], 1], 0, [[[...]|...], 1], 0] ;
L = [[h], 1, [[h], 1], 1, [[[h], 1], 1], 1, [[[...]|...], 1], 1] ;
false.
How can I make it correct?
Here's another way you could take...
Based on if_/3 and (=)/3 define list_hxys/2:
list_hxys([E|Es], [h|Xs]) :-
list_hxys_prev(Es, Xs, E).
list_hxys_prev([], [], _).
list_hxys_prev([E|Es], [X|Xs], E0) :-
if_(E = E0, X = y, X = x),
list_hxys_prev(Es, Xs, E).
Some sample queries using SICStus Prolog 4.3.2:
| ?- list_hxys([a,a,b,b], Xs). % (query given by the OP)
Xs = [h,y,x,y] ? ; % expected answer
no
| ?- list_hxys(As, [h,y,x,y]). % works the "other" way around, too
As = [_A,_A,_B,_B],
prolog:dif(_B,_A) ? ; % answer with residual goal dif/2
no
Let's break it down:
% Two elements being read are the same -> add y
control([H,H|T],[y|R]) :- control([H|T],R).
% Two elements being read are not the same -> add x
control([H1,H2|T],[x|R]) :- H1 \== H2, control([H2|T],R).
In both clauses we make a recursive call with all but the first checked element and respectively add an 'x' or 'y' to the result.
Now it's up to you to define the base case, note however that depending on whether input lists have an even or uneven amount of elements, two base cases will be required: one for a list with a single element and one for an empty list.

Prolog: Arrangements of k elements with sum of elements S

I am trying to compute arrangements of K elements in Prolog, where the sum of their elements is equal to a given S. So, I know that arrangements can be computed by finding the combinations and then permute them. I know how to compute combinations of K elements, something like:
comb([E|_], 1, [E]).
comb([_|T], K, R) :-
comb(T, K, R).
comb([H|T], K, [H|R]) :-
K > 1,
K1 is K-1,
comb(T, K1, R).
The permutations of a list, having the property that the sum of their elements is equal to a given S, I know to compute like this:
insert(E, L, [E|L]).
insert(E, [H|T], [H|R]) :-
insert(E, T, R).
perm([], []).
perm([H|T], P) :-
perm(T, R),
insert(H, R, P).
sumList([], 0).
sumList([H], H) :-
number(H).
sumList([H|Tail], R1) :-
sumList(Tail, R),
R1 is R+H.
perms(L, S, R) :-
perm(L, R),
sumList(R, S1),
S = S1.
allPerms(L, LP) :-
findall(R, perms(L,R), LP).
The problem is that I do not know how to combine them, in order to get the arrangements of K elements, having the sum of elements equal to a given S. Any help would be appreciated.
Use clpfd!
:- use_module(library(clpfd)).
Using SWI-Prolog 7.3.16 we query:
?- length(Zs,4), Zs ins 1..4, sum(Zs,#=,7), labeling([],Zs).
Zs = [1,1,1,4]
; Zs = [1,1,2,3]
; Zs = [1,1,3,2]
; Zs = [1,1,4,1]
; Zs = [1,2,1,3]
; Zs = [1,2,2,2]
; Zs = [1,2,3,1]
; Zs = [1,3,1,2]
; Zs = [1,3,2,1]
; Zs = [1,4,1,1]
; Zs = [2,1,1,3]
; Zs = [2,1,2,2]
; Zs = [2,1,3,1]
; Zs = [2,2,1,2]
; Zs = [2,2,2,1]
; Zs = [2,3,1,1]
; Zs = [3,1,1,2]
; Zs = [3,1,2,1]
; Zs = [3,2,1,1]
; Zs = [4,1,1,1].
To eliminate "redundant modulo permutation" solutions use chain/2:
?- length(Zs,4), Zs ins 1..4, chain(Zs,#=<), sum(Zs,#=,7), labeling([],Zs).
Zs = [1,1,1,4]
; Zs = [1,1,2,3]
; Zs = [1,2,2,2]
; false.
I use SWI-Prolog.
You can write that
:- use_module(library(lambda)).
arrangement(K, S, L) :-
% we have a list of K numbers
length(L, K),
% these numbers are between 1 (or 0) and S
maplist(between(1, S), L),
% the sum of these numbers is S
foldl(\X^Y^Z^(Z is X+Y), L, 0, S).
The result
?- arrangement(5, 10, L).
L = [1, 1, 1, 1, 6] ;
L = [1, 1, 1, 2, 5] ;
L = [1, 1, 1, 3, 4] ;
L = [1, 1, 1, 4, 3] .
You can use also a CLP(FD) library.
Edited after the remark of #repeat.
This response is similar to response of #repeat
predicates that below are implemented using the SICStus 4.3.2 tool
after simple modification of gen_list(+,+,?)
edit Code
gen_list(Length,Sum,List) :- length(List,Length),
domain(List,0,Sum),
sum(List,#=,Sum),
labeling([],List),
% to avoid duplicate results
ordered(List).
Test
| ?- gen_list(4,7,L).
L = [0,0,0,7] ? ;
L = [0,0,1,6] ? ;
L = [0,0,2,5] ? ;
L = [0,0,3,4] ? ;
L = [0,1,1,5] ? ;
L = [0,1,2,4] ? ;
L = [0,1,3,3] ? ;
L = [0,2,2,3] ? ;
L = [1,1,1,4] ? ;
L = [1,1,2,3] ? ;
L = [1,2,2,2] ? ;
no
I don't think that permutations could be relevant for your problem. Since the sum operation is commutative, the order of elements should be actually irrelevant. So, after this correction
sumList([], 0).
%sumList([H], H) :-
% number(H).
sumList([H|Tail], R1) :-
sumList(Tail, R),
R1 is R+H.
you can just use your predicates
'arrangements of K elements'(Elements, K, Sum, Arrangement) :-
comb(Elements, K, Arrangement),
sumList(Arrangement, Sum).
test:
'arrangements of K elements'([1,2,3,4,5,6],3,11,A).
A = [2, 4, 5] ;
A = [2, 3, 6] ;
A = [1, 4, 6] ;
false.
You already know how to use findall/3 to get all lists at once, if you need them.

How can I delete every occurrence of a sublist from a list in prolog?

This is the code for deleting or removing an element from a given list:
remove_elem(X,[],[]).
remove_elem(X,L1,L2) :-
L1 = [H|T],
X == H,
remove_elem(X,T,Temp),
L2 = Temp.
remove_elem(X,L1,L2) :-
L1 = [H|T],
X \== H,
remove_elem(X,T,Temp),
L2 = [H|Temp].
How can I modify it, so that I can delete every occurrence of a sub list from a list?
When I tried to put a list in an element, it only deletes the element and only once.
It should be this:
?- remove([1,2],[1,2,3,4,1,2,5,6,1,2,1],L).
L = [3,4,5,6,1]. % expected result
Inspired by #CapelliC's implementation I wrote the following code based on
and_t/3:
append_t([] ,Ys,Ys, true).
append_t([X|Xs],Ys,Zs,Truth) :-
append_aux_t(Zs,Ys,Xs,X,Truth).
append_aux_t([] ,_ ,_ ,_,false). % aux pred for using 1st argument indexing
append_aux_t([Z|Zs],Ys,Xs,X,Truth) :-
and_t(X=Z, append_t(Xs,Ys,Zs), Truth).
One append_t/4 goal can replace two prefix_of_t/3 and append/3 goals.
Because of that, the implementation of list_sublist_removed/3 gets a bit simpler than before:
list_sublist_removed([] ,[_|_] ,[]).
list_sublist_removed([X|Xs],[L|Ls],Zs) :-
if_(append_t([L|Ls],Xs0,[X|Xs]),
(Zs = Zs0 , Xs1 = Xs0),
(Zs = [X|Zs0], Xs1 = Xs)),
list_sublist_removed(Xs1,[L|Ls],Zs0).
Still deterministic?
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],[1,2],L).
L = [3,4,5,6,1].
Yes! What about the following?
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],X,[3,4,5,6,1]).
X = [1,2] ; % succeeds with useless choice-point
false.
Nope. So there is still room for potential improvement...
This logically pure implementation is based on the predicates if_/3 and (=)/3.
First, we build a reified version of prefix_of/2:
prefix_of_t([],_,true).
prefix_of_t([X|Xs],Zs,T) :-
prefix_of_t__aux(Zs,X,Xs,T).
prefix_of_t__aux([],_,_,false).
prefix_of_t__aux([Z|Zs],X,Xs,T) :-
if_(X=Z, prefix_of_t(Xs,Zs,T), T=false).
Then, on to the main predicate list_sublist_removed/3:
list_sublist_removed([],[_|_],[]).
list_sublist_removed([X|Xs],[L|Ls],Zs) :-
if_(prefix_of_t([L|Ls],[X|Xs]), % test
(Zs = Zs0, append([L|Ls],Xs0,[X|Xs])), % case 1
(Zs = [X|Zs0], Xs0 = Xs)), % case 2
list_sublist_removed(Xs0,[L|Ls],Zs0).
A few operational notes on the recursive clause of list_sublist_removed/3:
First (test), we check if [L|Ls] is a prefix of [X|Xs].
If it is present (case 1), we strip it off [X|Xs] yielding Xs0 and add nothing to Zs.
If it is absent (case 2), we strip X off [X|Xs] and add X to Zs.
We recurse on the rest of [X|Xs] until no more items are left to process.
Onwards to some queries!
The use case you gave in your question:
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],[1,2],L).
L = [3,4,5,6,1]. % succeeds deterministically
Two queries that try to find the sublist that was removed:
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],Sub,[ 3,4,5,6,1]).
Sub = [1,2] ? ;
no
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],Sub,[1,3,4,5,6,1]).
no
Next, let's find a suitable Ls in this query:
?- list_sublist_removed(Ls,[1,2],[3,4,5,6,1]).
% a lot of time passes ... and nothing happens!
Non-termination! This is unfortunate, but within expectations, as the solution set is infinite. However, by a-priori constraining the length of Ls, we can get all expected results:
?- length(Ls,_), list_sublist_removed(Ls,[1,2],[3,4,5,6,1]).
Ls = [ 3,4,5,6,1] ?
; Ls = [1,2, 3,4,5,6,1] ?
; Ls = [3, 1,2, 4,5,6,1] ?
; Ls = [3,4, 1,2, 5,6,1] ?
; Ls = [3,4,5, 1,2, 6,1] ?
; Ls = [3,4,5,6, 1,2, 1] ?
; Ls = [3,4,5,6,1, 1,2 ] ?
; Ls = [1,2, 1,2, 3,4,5,6,1] ? ...
<rant>
So many years I study Prolog, still it deserves some surprises... your problem it's quite simple to solve, when you know the list library, and you have a specific mode (like the one you posted as example). But can also be also quite complex to generalize, and it's unclear to me if the approach proposed by #repeat, based on #false suggestion (if_/3 and friends) can be 'ported' to plain, old Prolog (a-la Clocksin-Mellish, just to say).
</rant>
A solution, that has been not so easy to find, based on old-school Prolog
list_sublist_removed(L, S, R) :-
append([A, S, B], L),
S \= [],
list_sublist_removed(B, S, T),
append(A, T, R),
!
; L = R.
some test:
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],[1,2],L).
L = [3, 4, 5, 6, 1].
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],X,[3, 4, 5, 6, 1]).
X = [1, 2].
?- length(X,_), list_sublist_removed(X,[1,2],[3, 4, 5, 6, 1]).
X = [3, 4, 5, 6, 1] ;
X = [3, 4, 5, 6, 1, 2, 1] ...

remove first occurrence of an element in Prolog

I'm trying to remove the first occurrence of an element from a list in Prolog.
My code:
remove_first_X(X,[X|Xs],Xs). %remove X
remove_first_X(X,[Y|Xs],[Y|Xs]) :-
remove_first_X(X,Xs,Xs).
Doesn't work:
?- remove_first_X(1,[1,2,3],[2,3]).
true.
?- remove_first_X(1,[2,1,3],[2,3]).
false.
Please help! :-)
Another attempt is closer:
remove_first_X(X,[X|Xs],Xs).
remove_first_X(X,[Y|Xs],[Y|Ys]) :-
remove_first_X(X,Xs,Ys).
But removes X after its first occurrence:
?- remove_first_X(1,X,[2,1,0]).
X = [1, 2, 1, 0] ;
X = [2, 1, 1, 0] ;
X = [2, 1, 1, 0] ;
X = [2, 1, 0, 1] ;
false.
The implementation given by #chamini2 is impure, and can become logically unsound when working with non-ground terms. Consider the following two queries:
?- E=1, remove_first_X(E,Xs,[2,1,0]).
E = 1, Xs = [1,2,1,0] ;
E = 1, Xs = [2,1,1,0] ;
false.
?- remove_first_X(E,Xs,[2,1,0]), E=1.
E = 1, Xs = [1,2,1,0] ;
false. % one solution is missing!
prolog-dif to the rescue!
By replacing (\=)/2 with dif/2, the code gets logically pure:
remove_1st_x(X,[X|Xs],Xs).
remove_1st_x(X,[Y|Xs],[Y|Ys]) :-
dif(X,Y),
remove_1st_x(X,Xs,Ys).
Let's run above queries again, this time with the improved implementation:
?- E=1, remove_1st_x(E,Xs,[2,1,0]).
E = 1, Xs = [1,2,1,0] ;
E = 1, Xs = [2,1,1,0] ;
false.
?- remove_1st_x(E,Xs,[2,1,0]), E=1.
E = 1, Xs = [1,2,1,0] ;
E = 1, Xs = [2,1,1,0] ;
false.
That's better! And the other queries given by the OP also work like they should:
?- remove_1st_x(1,[1,2,3],[2,3]).
true ;
false.
?- remove_1st_x(1,[2,1,3],[2,3]).
true ;
false.
?- remove_1st_x(1,X,[2,1,0]).
X = [1,2,1,0] ;
X = [2,1,1,0] ;
false.
Edit 2015-05-07
Above implementation of remove_1st_x/3 leaves behind a useless choice-point when it could succeed deterministically.
Let's get rid of that inefficiency while preserving logical-purity!
Using if_/3 and reified equality (=)/3 (a.k.a. equal_truth/3), as defined by #false in an answer to question "Prolog union for A U B U C", we can define remove_1st_x/3 like this:
remove_1st_x(E,[X|Xs],Ys) :-
if_(X=E, Xs=Ys, (Ys=[X|Ys0],remove_1st_x(E,Xs,Ys0))).
Let's run above queries again! Note that all succeed deterministically.
?- remove_1st_x(1,[2,1,3],Ys).
Ys = [2,3].
?- remove_1st_x(1,[2,1,3],[2,3]).
true.
?- remove_1st_x(1,[1,2,3],[2,3]).
true.
try the adding one thing to the second attempt
remove_first_X(X,[X|Xs],Xs).
remove_first_X(X,[Y|Xs],[Y|Ys]) :-
X \= Y,
remove_first_X(X,Xs,Ys).
What happen in the example you ran was that
For X = [1, 2, 1, 0] it simply tried the first clause of remove_first_X
The next element was by going in the second clause and again to the first one, you can see that nothing prohibits that X = Y, that's something you should make sure of.

Fill list in SWI-Prolog

I am trying to fill a list of given length N with numbers 1,2,3,...,N.
I thought this could be done this way:
create_list(N,L) :-
length(L,N),
forall(between(1,N,X), nth1(X,L,X)).
However, this does not seem to work. Can anyone say what I am doing wrong?
First things first: Use clpfd!
:- use_module(library(clpfd)).
In the following I present zs_between_and/3, which (in comparison to my previous answer) offers some more features.
For a start, let's define some auxiliary predicates first!
equidistant_stride([] ,_).
equidistant_stride([Z|Zs],D) :-
equidistant_prev_stride(Zs,Z,D).
equidistant_prev_stride([] ,_ ,_). % internal predicate
equidistant_prev_stride([Z1|Zs],Z0,D) :-
Z1 #= Z0+D,
equidistant_prev_stride(Zs,Z1,D).
Let's run a few queries to get a picture of equidistant_stride/2:
?- Zs = [_,_,_], equidistant_stride(Zs,D).
Zs = [_A,_B,_C], _A+D#=_B, _B+D#=_C.
?- Zs = [1,_,_], equidistant_stride(Zs,D).
Zs = [1,_B,_C], _B+D#=_C, 1+D#=_B.
?- Zs = [1,_,_], equidistant_stride(Zs,10).
Zs = [1,11,21].
So far, so good... moving on to the actual "fill list" predicate zs_between_and/3:
zs_between_and([Z0|Zs],Z0,Z1) :-
Step in -1..1,
Z0 #= Z1 #<==> Step #= 0,
Z0 #< Z1 #<==> Step #= 1,
Z0 #> Z1 #<==> Step #= -1,
N #= abs(Z1-Z0),
( fd_size(N,sup)
-> true
; labeling([enum,up],[N])
),
length(Zs,N),
labeling([enum,down],[Step]),
equidistant_prev_stride(Zs,Z0,Step).
A bit baroque, I must confess...
Let's see what features were gained---in comparison to my previous answer!
?- zs_between_and(Zs,1,4). % ascending consecutive integers
Zs = [1,2,3,4]. % (succeeds deterministically)
?- zs_between_and(Zs,3,1). % descending consecutive integers (NEW)
Zs = [3,2,1]. % (succeeds deterministically)
?- zs_between_and(Zs,L,10). % enumerates fairly
L = 10, Zs = [10] % both ascending and descenting (NEW)
; L = 9, Zs = [9,10]
; L = 11, Zs = [11,10]
; L = 8, Zs = [8,9,10]
; L = 12, Zs = [12,11,10]
; L = 7, Zs = [7,8,9,10]
...
?- L in 1..3, zs_between_and(Zs,L,6).
L = 3, Zs = [3,4,5,6]
; L = 2, Zs = [2,3,4,5,6]
; L = 1, Zs = [1,2,3,4,5,6].
Want some more? Here we go!
?- zs_between_and([1,2,3],From,To).
From = 1, To = 3
; false.
?- zs_between_and([A,2,C],From,To).
A = 1, From = 1, C = 3, To = 3 % ascending
; A = 3, From = 3, C = 1, To = 1. % descending
I don't have a prolog interpreter available right now, but wouldn't something like...
isListTo(N, L) :- reverse(R, L), isListFrom(N, R).
isListFrom(0, []).
isListFrom(N, [H|T]) :- M is N - 1, N is H, isListFrom(M, T).
reverse can be done by using e.g. http://www.webeks.net/prolog/prolog-reverse-list-function.html
So tracing isListTo(5, [1, 2, 3, 4, 5])...
isListTo(5, [1, 2, 3, 4, 5])
<=> isListFrom(5, [5, 4, 3, 2, 1])
<=> 5 is 5 and isListFrom(4, [4, 3, 2, 1])
<=> 4 is 4 and isListFrom(3, [3, 2, 1])
<=> 3 is 3 and isListFrom(2, [2, 1])
<=> 2 is 2 and isListFrom(1, [1])
<=> 1 is 1 and isListFrom(0, [])
QED
Since PROLOG will not only evaluate truth, but find satisfying solutions, this should work. I know this is a vastly different approach from the one you are trying, and apologize if your question is specifically about doing loops in PROLOG (if that is the case, perhaps re-tag the question?).
Here's a logically pure implementation of predicate zs_from_to/3 using clpfd:
:- use_module(library(clpfd)).
zs_from_to([],I0,I) :-
I0 #> I.
zs_from_to([I0|Is],I0,I) :-
I0 #=< I,
I1 #= I0 + 1,
zs_from_to(Is,I1,I).
Let's use it! First, some ground queries:
?- zs_from_to([1,2,3],1,3).
true.
?- zs_from_to([1,2,3],1,4).
false.
Next, some more general queries:
?- zs_from_to(Zs,1,7).
Zs = [1,2,3,4,5,6,7]
; false.
?- zs_from_to([1,2,3],From,To).
From = 1, To = 3.
Now, let's have some even more general queries:
?- zs_from_to(Zs,From,2).
Zs = [], From in 3..sup
; Zs = [2], From = 2
; Zs = [1,2], From = 1
; Zs = [0,1,2], From = 0
; Zs = [-1,0,1,2], From = -1
; Zs = [-2,-1,0,1,2], From = -2
...
?- zs_from_to(Zs,0,To).
Zs = [], To in inf.. -1
; Zs = [0], To = 0
; Zs = [0,1], To = 1
; Zs = [0,1,2], To = 2
; Zs = [0,1,2,3], To = 3
; Zs = [0,1,2,3,4], To = 4
...
What answers do we get for the most general query?
?- zs_from_to(Xs,I,J).
Xs = [], J#=<I+ -1
; Xs = [I], I+1#=_A, J#>=I, J#=<_A+ -1
; Xs = [I,_A], I+1#=_A, J#>=I, _A+1#=_B, J#>=_A, J#=<_B+ -1
; Xs = [I,_A,_B], I+1#=_A, J#>=I, _A+1#=_B, J#>=_A, _B+1#=_C, J#>=_B, J#=<_C+ -1
...
Edit 2015-06-07
To improve on above implementation of zs_from_to/3, let's do two things:
Try to improve determinism of the implementation.
Extract a more general higher-order idiom, and implement zs_from_to/3 on top of it.
Introducing the meta-predicates init0/3 and init1/3:
:- meta_predicate init0(2,?,?).
:- meta_predicate init1(2,?,?).
init0(P_2,Expr,Xs) :- N is Expr, length(Xs,N), init_aux(Xs,P_2,0).
init1(P_2,Expr,Xs) :- N is Expr, length(Xs,N), init_aux(Xs,P_2,1).
:- meta_predicate init_aux(?,2,+). % internal auxiliary predicate
init_aux([] , _ ,_ ).
init_aux([Z|Zs],P_2,I0) :-
call(P_2,I0,Z),
I1 is I0+1,
init_aux(Zs,P_2,I1).
Let's see init0/3 and init1/3 in action!
?- init0(=,5,Zs). % ?- numlist(0,4,Xs),maplist(=,Xs,Zs).
Zs = [0,1,2,3,4].
?- init1(=,5,Zs). % ?- numlist(1,5,Xs),maplist(=,Xs,Zs).
Zs = [1,2,3,4,5].
Ok, where do we go from here? Consider the following query:
?- init0(plus(10),5,Zs). % ?- numlist(0,4,Xs),maplist(plus(10),Xs,Zs).
Zs = [10,11,12,13,14].
Almost done! Putting it together, we define zs_from_to/2 like this:
z_z_sum(A,B,C) :- C #= A+B.
zs_from_to(Zs,I0,I) :-
N #= I-I0+1,
init0(z_z_sum(I0),N,Zs).
At last, let's see if determinism has improved!
?- zs_from_to(Zs,1,7).
Zs = [1,2,3,4,5,6,7]. % succeeds deterministically
If I understood correctly, the built-in predicate numlist/3 would do.
http://www.swi-prolog.org/pldoc/man?predicate=numlist/3