I want to formulate a constraint in SWI-Prolog, using CLP (FD, in particular), that a list is a cyclical ascending list.
By that I mean a regular Prolog list which is taken to represent a cyclical list, such that the list and all its rotations represent the same cyclical list. And the constraint is that one of those rotations is a strictly ascending list.
For example, for 8 variables, I could represent it like this:
cyclical_ascending([A,B,C,D,E,F,G,H]) :-
B #> A,
C #> B,
D #> C,
E #> D,
F #> E,
G #> F,
H #> G,
A #> H.
except that one of those constraints is bound to not hold, while all the others are to hold. And I don't know/care, which one.
How can this be done?
There are a couple of ways I've thought of defining a cyclical_ascending
rule:
cyclical_ascending
if one of the rotations of the list is
ascendingcyclical_ascending
if either (a) there are no adjacent pairs X, Y
where X >= Y
, or (b) there is only one such pair and Head > Tail
.I think the second definition leads to a more efficient solution, so I'll try that. We'll keep track of the head of the list, and keep count of whether there was a single
:- use_module(library(clpfd)).
cyclical_ascending([]). % Empty list is a degenerate cyclical ascending list
cyclical_ascending([H|T]) :-
cyclical_ascending([H|T], H, 0).
cyclical_ascending([_], _, 0). % List is ascending
cyclical_ascending([X], H, 1) :- % A cycle of list is ascending
X #< H.
cyclical_ascending([X,Y|T], H, C) :-
X #< Y,
cyclical_ascending([Y|T], H, C).
cyclical_ascending([X,Y|T], H, C) :-
X #>= Y,
C #< 1,
C1 #= C + 1,
cyclical_ascending([Y|T], H, C1).
Or another way to write it is to avoid the counter but use another auxiliary predicate:
cyclical_ascending([]). % Empty list is a degenerate cyclical ascending list
cyclical_ascending([H|T]) :-
cyclical_ascending([H|T], H).
cyclical_ascending([_], _).
cyclical_ascending([X,Y|T], H) :-
X #< Y,
cyclical_ascending([Y|T], H).
cyclical_ascending([X,Y|T], H) :-
X #>= Y,
cyclical_ascending1([Y|T], H).
cyclical_ascending1([X], H) :-
X #< H.
cyclical_ascending1([X,Y|T], H) :-
X #< Y,
cyclical_ascending1([Y|T], H).
Trying a simple query:
2 ?- length(L, 4), L ins 1..4, cyclical_ascending(L).
L = [1, 2, 3, 4] ;
L = [2, 3, 4, 1] ;
L = [3, 4, 1, 2] ;
L = [4, 1, 2, 3] ;
false.
3 ?-