4

How can I limit the repetition of a number in a list?

What is a suitable constraint in the following code example?

limit(X) :-
    length(X,10),
    domain(X,1,4),
    % WANTED CONSTRAINT: maximum repetition of each number is 5 times.
    labeling([],X).

Some sample queries and expected answers:

?- limit([1,1,1,1,1,1,1,1,1]).
false.

?- limit([1,1,1,1,1,2,2,2,2,2]).
true.
repeat
  • 18,496
  • 4
  • 54
  • 166

4 Answers4

2

This works, L is the list of the number of repetitions of each number from 1 to 4.

:- use_module(library(clpfd)).

limit(X) :-
    length(L, 4),
    L ins 0..5,
    sum(L, #=, 10),
    label(L),    
    maplist(make_list, [1,2,3,4], L, LX),
    flatten([LX],X).


make_list(Val, Nb, L) :-
    length(L, Nb),
    L ins Val .. Val.

The problem is that the numbers are group by values. The code may be generalized to

limit(X, Min, Max, Len, Rep) :-
    Nb is Max -Min + 1,
    length(L, Nb),
    L ins 0..Rep,
    sum(L, #=, Len),
    label(L),
    numlist(Min, Max, Lst),
    maplist(make_list, Lst, L, LX),
    flatten([LX],X).

You try : limit(X, 1, 4, 10, 5).

joel76
  • 5,565
  • 1
  • 18
  • 22
  • 1
    `Ls ins Val..Val` is a neat usage of `ins/2`, very nice! As an alternative which is maybe more readable, consider: `maplist(=(Val), Ls)`. – mat Mar 31 '13 at 22:09
2

In this answer we use two different "flavors": and .

:- use_module(library(clpfd)).

limited_repetitions__SICStus(Zs) :-
   length(Zs, 10),
   domain(Zs, 1, 4),
   domain([C1,C2,C3,C4], 0, 5),
   global_cardinality(Zs, [1-C1,2-C2,3-C3,4-C4]),
   labeling([], Zs).

limited_repetitions__gprolog(Zs) :-
   length(Zs, 10),
   fd_domain(Zs, 1, 4),
   maplist(fd_atmost(5,Zs), [1,2,3,4]),
   fd_labeling(Zs).

Simple sample query run with SICStus Prolog version 4.3.2 and GNU Prolog 1.4.4:

?- limited_repetitions__SICStus(Zs).   %  ?- limited_repetitions__gprolog(Zs).
  Zs = [1,1,1,1,1,2,2,2,2,2]           %    Zs = [1,1,1,1,1,2,2,2,2,2]
; Zs = [1,1,1,1,1,2,2,2,2,3]           %  ; Zs = [1,1,1,1,1,2,2,2,2,3]
; Zs = [1,1,1,1,1,2,2,2,2,4]           %  ; Zs = [1,1,1,1,1,2,2,2,2,4]
; Zs = [1,1,1,1,1,2,2,2,3,2]           %  ; Zs = [1,1,1,1,1,2,2,2,3,2]
; Zs = [1,1,1,1,1,2,2,2,3,3]           %  ; Zs = [1,1,1,1,1,2,2,2,3,3]
; Zs = [1,1,1,1,1,2,2,2,3,4]           %  ; Zs = [1,1,1,1,1,2,2,2,3,4]
; Zs = [1,1,1,1,1,2,2,2,4,2]           %  ; Zs = [1,1,1,1,1,2,2,2,4,2] 
...                                    %  ...

Let's measure the time required for counting the number of solutions!

call_succeeds_n_times(G_0, N) :-
   findall(t, call(G_0), Ts),
   length(Ts, N).

?- call_time(call_succeeds_n_times(limited_repetitions__SICStus(_), N), T_ms).
N = 965832, T_ms = 6550.               % w/SICStus Prolog 4.3.2

?- call_time(call_succeeds_n_times(limited_repetitions__gprolog(_), N), T_ms).
N = 965832, T_ms = 276.                % w/GNU Prolog 1.4.4
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
2

In this previous answer we utilized the SICStus Prolog predicate global_cardinality/2. As an non-constraint alternative, we could also use selectd/3 like this:

multi_selectd_rest([],Ds,Ds).
multi_selectd_rest([Z|Zs],Ds0,Ds) :-
   selectd(Z,Ds0,Ds1),
   multi_selectd_rest(Zs,Ds1,Ds).

Putting it to good use in limited_repetitions__selectd/3 we define:

limited_repetitions__selectd(Zs) :-
   length(Zs, 10),
   multi_selectd_rest(Zs,[1,1,1,1,1,2,2,2,2,2,3,3,3,3,3,4,4,4,4,4],_).

Again, let's measure the time required for counting the number of solutions!

?- call_time(call_succeeds_n_times(limited_repetitions__selectd(_),N), T_ms).
N = 965832, T_ms = 4600.
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
1

Here is a way, but not for sequences:

:- [library(clpfd)].

limit_repetition(Xs, Max) :-
    maplist(vs_n_num(Xs, Max), Xs).

vs_n_num(Vs, Max, X) :-
    maplist(eq_b(X), Vs, Bs),
%   sum(Bs, #=, EqC),
%   EqC #=< Max.
    sum(Bs, #=<, Max).

eq_b(X, Y, B) :- X #= Y #<==> B.

vs_n_num/3 is an adapted version of what you can find in docs.

Here's a way to delimite sequences:

limit_repetition([X|Xs], Max) :-
    limit_repetition(X, 1, Xs, Max).

limit_repetition(X, C, [Y|Xs], Max) :-
    X #= Y #<==> B,
    ( B #/\ C + B #=< Max #/\ D #= C + B ) #\/ ( (#\ B) #/\ D #= 1 ),
    limit_repetition(Y, D, Xs, Max).
limit_repetition(_X, _C, [], _Max).

yields

?- length(X,4), X ins 1..4, limit_repetition(X, 1) ,label(X).
X = [1, 2, 1, 2] ;
X = [1, 2, 1, 3] ;
...

Seems the former version is more related to your sample.

CapelliC
  • 59,646
  • 5
  • 47
  • 90