Constrain two lists to begin with N consecutive elements in total using CLP(FD)

I am trying to constrain two lists to begin with N consecutive elements (E) in total using CLP(FD). Here's an example: let L1 and L2 be two lists of size 6, the elements belong to the domain [0, 1], E = 1, and N = 3, then the predicate constraint(+L1, +L2, +N) would provide the following possible solutions:

L1 = [1, 1, 1, 0, _, _], L2 = [0, _, _, _, _, _];
L1 = [1, 1, 0, _, _, _], L2 = [1, 0, _, _, _, _];
L1 = [1, 0, _, _, _, _], L2 = [1, 1, 0, _, _, _];
L1 = [0, _, _, _, _, _], L2 = [1, 1, 1, 0, _, _].

For lists of size 3, the following would be acceptable:

L1 = [1, 1, 1], L2 = [0, _, _];
L1 = [1, 1, 0], L2 = [1, 0, _];
L1 = [1, 0, _], L2 = [1, 1, 0];
L1 = [0, _, _], L2 = [1, 1, 1].

I eventually want to generalize this to an arbitrary number of lists and domain, but this is the smallest equivalent problem I could think of.


Here's my (failed) attempt so far:

:- use_module(library(clpfd)).

constseq([], _, 0).
constseq([L|_], A, 0) :- L #\= A.
constseq([A|Ls], A, N) :- N1 #= N - 1, constseq(Ls, A, N1).

constraint(L1, L2, N) :-
  SL1 + SL2 #= N,
  constseq(L1, 1, SL1),
  constseq(L2, 1, SL2).

main(L1, L2) :-
  length(L1, 6),
  length(L2, 6),
  constraint(L1, L2, 3).

Although it works, note that I'm generating the solutions through backtracking, and not taking advantage of CLP(FD) to do the dirty job. I'm trying to figure out how to accomplish this, and I'm already looking at predicates like chain/2, and monsters like automaton/3, but something in me tells that there must be a simpler solution to this...

Upvotes: 4

Views: 154

Answers (2)

jschimpf
jschimpf

Reputation: 5034

I'd write it as follows (using ECLiPSe with library(ic)):

:- lib(ic).
:- lib(ic_global).

constraint(Xs, Ys, N) :-
    Xs #:: 0..1,
    Ys #:: 0..1,
    sum(Xs) + sum(Ys) #= N,
    ordered(>=, Xs),
    ordered(>=, Ys).

which gives the desired solutions:

?- length(Xs,6), length(Ys,6), constraint(Xs,Ys,3), labeling(Xs), labeling(Ys).
Xs = [0, 0, 0, 0, 0, 0]
Ys = [1, 1, 1, 0, 0, 0]
Yes (0.00s cpu, solution 1, maybe more) ? ;
Xs = [1, 0, 0, 0, 0, 0]
Ys = [1, 1, 0, 0, 0, 0]
Yes (0.00s cpu, solution 2, maybe more) ? ;
Xs = [1, 1, 0, 0, 0, 0]
Ys = [1, 0, 0, 0, 0, 0]
Yes (0.00s cpu, solution 3, maybe more) ? ;
Xs = [1, 1, 1, 0, 0, 0]
Ys = [0, 0, 0, 0, 0, 0]
Yes (0.00s cpu, solution 4)

Upvotes: 0

Inspired on SICStus example of exactly/3, here's my latest attempt:

constseq_(_, [], _, 0).
constseq_(X, [Y|L], F, N) :-
  X #= Y #/\ F #<=> B,
  N #= M+B,
  constseq_(X, L, B, M).

constseq(L, E, N) :-
  constseq_(E, L, 1, N).

Upvotes: 3

Related Questions