简体   繁体   中英

Is it possible to declare an ascending list?

I can make lists of ascending integer like so:

?- findall(L,between(1,5,L),List).

I know I can also generate values using:

?- length(_,X).

But I don't think I can use this in a findall, as things like the following loop:

?- findall(X,(length(_,X),X<6),Xs).

I can also generate a list using .

:- use_module(library(clpfd)).

list_to_n(N,List) :-
   length(List,N),
   List ins 1..N,
   all_different(List),
   once(label(List)).

or

list_to_n2(N,List) :-
   length(List,N),
   List ins 1..N,
   chain(List,#<),
   label(List).

The last method seems best to me as it is the most declarative, and does not use once/1 or between/3 or findall/3 etc.

Are there other ways to do this? Is there a declarative way to do this in 'pure' Prolog? Is there a 'best' way?

The "best" way depends on your concrete use cases! Here's another way to do it using :

:- use_module(library(clpfd)).

We define predicate equidistant_stride/2 as suggested by @mat in a comment to a previous answer of a related question :

equidistant_stride([],_).
equidistant_stride([Z|Zs],D) :- 
   foldl(equidistant_stride_(D),Zs,Z,_).

equidistant_stride_(D,Z1,Z0,Z1) :-
   Z1 #= Z0+D.

Based on equidistant_stride/2 , we define:

consecutive_ascending_integers(Zs) :-
   equidistant_stride(Zs,1).

consecutive_ascending_integers_from(Zs,Z0) :-
   Zs = [Z0|_],
   consecutive_ascending_integers(Zs).

consecutive_ascending_integers_from_1(Zs) :-
   consecutive_ascending_integers_from(Zs,1).

Let's run some queries! First, your original use case:

?- length(Zs,N), consecutive_ascending_integers_from_1(Zs).
  N = 1, Zs = [1]
; N = 2, Zs = [1,2]
; N = 3, Zs = [1,2,3]
; N = 4, Zs = [1,2,3,4]
; N = 5, Zs = [1,2,3,4,5]
...

With , we can ask quite general queries—and get logically sound answers, too!

?- consecutive_ascending_integers([A,B,,D,E]).
A = -2, B = -1, D = 1, E = 2.

?- consecutive_ascending_integers([A,B,C,D,E]).
A+1#=B, B+1#=C, C+1#=D, D+1#=E.

An alternative implementation of equidistant_stride/2 :

I hope the new code makes better use of constraint propagation.

Thanks to @WillNess for suggesting the test-cases that motivated this rewrite!

equidistant_from_nth_stride([],_,_,_).
equidistant_from_nth_stride([Z|Zs],Z0,N,D) :-
   Z  #= Z0 + N*D,
   N1 #= N+1,
   equidistant_from_nth_stride(Zs,Z0,N1,D).

equidistant_stride([],_).
equidistant_stride([Z0|Zs],D) :-
   equidistant_from_nth_stride(Zs,Z0,1,D).

Comparison of old vs new version with @mat's clpfd:

First up, the old version:

?- equidistant_stride([1,_,_,_,14],D).
_G1133+D#=14,
_G1145+D#=_G1133,
_G1157+D#=_G1145,
1+D#=_G1157.                               % succeeds with Scheinlösung

?- equidistant_stride([1,_,_,_,14|_],D).
  _G1136+D#=14, _G1148+D#=_G1136, _G1160+D#=_G1148, 1+D#=_G1160
; 14+D#=_G1340, _G1354+D#=14, _G1366+D#=_G1354, _G1378+D#=_G1366, 1+D#=_G1378
...                                        % does not terminate universally

Now let's switch to the new version and ask the same queries!

?- equidistant_stride([1,_,_,_,14],D).      
.                                     % fails, as it should

?- equidistant_stride([1,_,_,_,14|_],D).
.                                     % fails, as it should

More, now, again! Can we fail earlier by tentatively employing redundant constraints?

Previously, we proposed using constraints Z1 #= Z0+D*1, Z2 #= Z0+D*2, Z3 #= Z0+D*3 instead of Z1 #= Z0+D, Z2 #= Z1+D, Z3 #= Z2+D (which the 1st version of code in this answer did).

Again, thanks to @WillNess for motivating this little experiment by noting that the goal equidistant_stride([_,4,_,_,14],D) does not fail but instead succeeds with pending goals:

?- Zs = [_,4,_,_,14], equidistant_stride(Zs,D).
Zs = [_G2650, 4, _G2656, _G2659, 14],
14#=_G2650+4*D,
_G2659#=_G2650+3*D,
_G2656#=_G2650+2*D,
_G2650+D#=4.

Let's add some redundant constraints with equidistantRED_stride/2 :

equidistantRED_stride([],_).
equidistantRED_stride([Z|Zs],D) :-
   equidistant_from_nth_stride(Zs,Z,1,D),
   equidistantRED_stride(Zs,D).

Sample query:

?- Zs = [_,4,_,_,14], equidistant_stride(Zs,D), equidistantRED_stride(Zs,D).
false.

Done? Not yet! In general we don't want a quadratic number of redundant constraints. Here's why:

?- Zs = [_,_,_,_,14], equidistant_stride(Zs,D).
Zs = [_G2683, _G2686, _G2689, _G2692, 14],
14#=_G2683+4*D,
_G2692#=_G2683+3*D,
_G2689#=_G2683+2*D,
_G2686#=_G2683+D.

?- Zs = [_,_,_,_,14], equidistant_stride(Zs,D), equidistantRED_stride(Zs,D).
Zs = [_G831, _G834, _G837, _G840, 14],
14#=_G831+4*D,
_G840#=_G831+3*D,
_G837#=_G831+2*D,
_G834#=_G831+D,
14#=_G831+4*D,
_G840#=_G831+3*D,
_G837#=_G831+2*D,
_G834#=_G831+D,
D+_G840#=14,
14#=2*D+_G837,
_G840#=D+_G837,
14#=_G834+3*D,
_G840#=_G834+2*D,
_G837#=_G834+D.

But if we use the double-negation trick, the residuum remains in cases that succeed ...

?- Zs = [_,_,_,_,14], equidistant_stride(Zs,D), \+ \+ equidistantRED_stride(Zs,D).
Zs = [_G454, _G457, _G460, _G463, 14],
14#=_G454+4*D,
_G463#=_G454+3*D,
_G460#=_G454+2*D,
_G457#=_G454+D.

... and ...

?- Zs = [_,4,_,_,14], equidistant_stride(Zs,D), \+ \+ equidistantRED_stride(Zs,D).
.

... we detect failure in more cases than we did before!


Let's dig a little deeper! Can we detect failure early in even more generalized uses?

With code presented so far, these two logically false queries do not terminate:

?- Zs = [_,4,_,_,14|_], \+ \+ equidistantRED_stride(Zs,D), equidistant_stride(Zs,D).
...                                        % 

?- Zs = [_,4,_,_,14|_], equidistant_stride(Zs,D), \+ \+ equidistantRED_stride(Zs,D).
...                                        % 

Got fix? Got hack!

?- use_module(library(lambda)).
true.

?- Zs = [_,4,_,_,14|_], 
   \+ ( term_variables(Zs,Vs), 
        maplist(\X^when(nonvar(X),integer(X)),Vs),
        \+ equidistantRED_stride(Zs,D)),
   equidistant_stride(Zs,D).
.

The hack doesn't guarantee termination of the redundant constraint "part", but IMO it's not too bad for a quick first shot. The test integer/1 upon instantiation of any variable in Zs is meant to allow the solver to constrain variable domains to singletons, while the instantiation with cons-pairs (which directly leads to non-termination of list-based predicates) is suppressed.

I do realize that the hack can be broken quite easily in more than one way (eg, using cyclic terms). Any suggestions and comments are welcome!

In the following we discuss the code presented in this previous answer .

The goal consecutive_ascending_integers_from_1([2,3,5,8|non_list]) fails, but why?

Let's proceed step-by-step:

  1. Here's the code we start with:

    \n:- use_module(library(clpfd)). \n\nequidistant_from_nth_stride([],_,_,_). \nequidistant_from_nth_stride([Z|Zs],Z0,I0,D) :- \n   Z #= Z0 + I0*D, \n   I1 #= I0 + 1, \n   equidistant_from_nth_stride(Zs,Z0,I1,D). \n\nequidistant_stride([],_). \nequidistant_stride([Z0|Zs],D) :- \n   equidistant_from_nth_stride(Zs,Z0,1,D). \n\nconsecutive_ascending_integers(Zs) :- \n   equidistant_stride(Zs,1). \n\nconsecutive_ascending_integers_from(Zs,Z0) :- \n   Zs = [Z0|_], \n   consecutive_ascending_integers(Zs). \n\nconsecutive_ascending_integers_from_1(Zs) :- \n   consecutive_ascending_integers_from(Zs,1). \n
  2. First, we make (some) unifications more explicit:

    \nequidistant_from_nth_stride([],_,_,_). \nequidistant_from_nth_stride([Z|Zs],Z0,I0,D) :- \n   Z #= Z0 + I0*D, \n   I1 #= I0 + 1, \n   equidistant_from_nth_stride(Zs,Z0,I1,D). \n\nequidistant_stride([],_). \nequidistant_stride([Z0|Zs],D) :- \n    ,  ,\n   equidistant_from_nth_stride(Zs,Z0,  ,D).  ,D)。\n\nconsecutive_ascending_integers(Zs) :- \n    ,  ,\n   equidistant_stride(Zs,  ).  )。\n\nconsecutive_ascending_integers_from(Zs,Z0) :- \n    ,  ,\n   consecutive_ascending_integers(Zs). \n\nconsecutive_ascending_integers_from_1(Zs) :- \n    ,  ,\n   consecutive_ascending_integers_from(Zs,  ).  )。\n
  3. We follow the method and conventions introduced in this fine answer :

    By removing goals, we can generalize a program. Here is my favorite way to do it. By adding a predicate (*)/1 like so:

    \n:- op(950,fy, *). \n\n*_. \n
  4. @WillNess rightly noted that:

    consecutive_ascending_integers_from_1([2|_]) fails, so its specialization consecutive_ascending_integers_from_1([2,3,5,8|non_list]) must fail too.

    If maximally generalize the code so that consecutive_ascending_integers_from_1([2|_]) fails, we "know for sure: something in the visible remaining part of the program has to be fixed."

consecutive_ascending_integers_from(Zs,Z0) :-
       Zs = [Z0|_],
       * consecutive_ascending_integers(Zs).

    consecutive_ascending_integers_from_1(Zs) :-
       Start = 1,
       consecutive_ascending_integers_from(Zs,Start).
  1. Let's have another explanation!

    With version #2 (see above), we observe the following generalized goal fails, too:

    \n?- consecutive_ascending_integers_from_1([_,_,_,_|non_list]). \nfalse. \n

    Why does this fail? Let's maximally generalize the code suchthat the goal fails:

equidistant_from_nth_stride([],_,_,_).
    equidistant_from_nth_stride([Z|Zs],Z0,I0,D) :-
       * Z  #= Z0 + I0*D,
       * I1 #= I0 + 1,
       equidistant_from_nth_stride(Zs,Z0,I1,D).

    equidistant_stride([],_).
    equidistant_stride([Z0|Zs],D) :-
       * I = 1,
       equidistant_from_nth_stride(Zs,Z0,I,D).

    consecutive_ascending_integers(Zs) :-
       * D = 1,
       equidistant_stride(Zs,D).

    consecutive_ascending_integers_from(Zs,Z0) :-
       * Zs = [Z0|_],
       consecutive_ascending_integers(Zs).

    consecutive_ascending_integers_from_1(Zs) :-
       * Start = 1,
       consecutive_ascending_integers_from(Zs,Start).

Why does the goal consecutive_ascending_integers_from_1([2,3,5,8|non_list]) fail?

Up to now, we have seen two explanations, but there may be more...

The truth is out there: Join the hunt!

We'll define ascending lists as such that contain at least two elements which are increasing integer numbers ( non-decreasing lists could be empty, or singleton, but "ascending" is a more definite property). It's a somewhat arbitrary determination.

In SWI Prolog:

ascending( [A,B|R] ):-
   freeze(A, 
      freeze(B, (A < B, freeze(R, (R=[] -> true ; ascending([B|R])))) )).

To easily fill'em up, we could use

mselect([A|B],S,S2):- select(A,S,S1), mselect(B,S1,S2).
mselect([], S2, S2).

Testing:

15 ?- ascending(LS),mselect(LS,[10,2,8,5],[]).
LS = [2, 5, 8, 10]

16 ?- mselect(LS,[10,2,8,5],[]), ascending(LS).
LS = [2, 5, 8, 10]


As to the bounty question, according to https://stackoverflow.com/tags/logical-purity/info ,

Only monotonic (also called: "monotone") predicates are pure: If the predicate succeeds for any arguments, then it does not fail for any generalization of these arguments, and if it fails for any combination of arguments, then it does not succeed for any specialization of these arguments.

consecutive_ascending_integers_from_1([2|B]) fails, so its specialization consecutive_ascending_integers_from_1([2,3,5,8|non_list]) must fail too.


For the extended bounty " consecutive_ascending_integers_from_1([2,3,5,8|non_list]) fails, but why?" , additional failing goals are: ( 1 )

consecutive_ascending_integers_from_1([_,3|_])

for the code

equidistant_from_nth_stride([],_,_,_).     
equidistant_from_nth_stride([Z|Zs],Z0,I0,D) :-
   Z  #= Z0 + I0*D,                        % C1
   *( I1 #= I0 + 1 ),
   equidistant_from_nth_stride(Zs,Z0,I1,D).

and the rest unchanged, because C1 becomes 3 #= 1 + 1*1 . Also, ( 2 and 3 )

consecutive_ascending_integers_from_1([A,B,5|_])
consecutive_ascending_integers_from_1([A,B,C,8|_])

both fail with the unchanged code, because the 1st defines

A = 1, B #= 1 + 1*1, 5 #= 1 + 2*1

and the 2nd defines

A = 1, B #= 1 + 1*1, C #= 1 + 2*1, 8 #= 1 + 3*1

Yet another possibility ( 4 ) is

consecutive_ascending_integers_from_1([_,3,5|_])

with the generalized

consecutive_ascending_integers_from_1(Zs) :-
   *( Z0 = 1 ),
   consecutive_ascending_integers_from(Zs,Z0).

consecutive_ascending_integers_from(Zs,Z0) :-
   *( Zs = [Z0|_] ),
   consecutive_ascending_integers(Zs).

because

26 ?- 3 #= Z + 1*1, 5 #= Z + 2*1.
false.

Similarly, with the like modified code, the goal ( 5 )

consecutive_ascending_integers_from_1([_,3,_,8|_])

because

27 ?- 3 #= Z + 1*1, 8 #= Z + 3*1.
false.

and also the ( 6 ... 9 )

consecutive_ascending_integers_from_1([2,3,_,8|_])
consecutive_ascending_integers_from_1([2,_,_,8|_])
consecutive_ascending_integers_from_1([2,_,5,8|_])
consecutive_ascending_integers_from_1([2,_,5|_])

for the same reason. Yet another possible code generalization is to leave D uninitialized (with the rest of the original code unchanged):

consecutive_ascending_integers(Zs) :-
   *( D = 1 ),
   equidistant_stride(Zs,D).

so that the goal ( 5 ) ...[_,3,_,8|_]... again fails, because of

49 ?- 3 #= 1 + 1*D, 8 #= 1 + 3*D.
false.

but,

50 ?- 3 #= 1 + 1*D, 5 #= 1 + 2*D.
D = 2.

so ...[_,3,5|_]... would succeed (indeed it does). ( 10 )

consecutive_ascending_integers_from_1([_,_,5,8|_])

fails, as well, for the same reason.

There might be some more combinations, but the general gist of it becomes clearer: it all depends on how the constraints created by this predicate operate.

The technical post webpages of this site follow the CC BY-SA 4.0 protocol. If you need to reprint, please indicate the site URL or the original address.Any question please contact:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM