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:
开发者_如何学JAVAcreate_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
精彩评论