Tennis match scheduling

Preface

In Prolog, CLP(FD) constraints are the right choice for solving such scheduling tasks.

See clpfd for more information.

In this case, I suggest using the powerful global_cardinality/2 constraint to restrict the number of occurrences of each round, depending on the number of available courts. We can use iterative deepening to find the minimal number of admissible rounds.

Freely available Prolog systems suffice to solve the task satisfactorily. Commercial-grade systems will run dozens of times faster.

Variant 1: Solution with SWI-Prolog

:- use_module(library(clpfd)).

tennis(N, Courts, Rows) :-
        length(Rows, N),
        maplist(same_length(Rows), Rows),
        transpose(Rows, Rows),
        Rows = [[_|First]|_],
        chain(First, #<),
        length(_, MaxRounds),
        numlist(1, MaxRounds, Rounds),
        pairs_keys_values(Pairs, Rounds, Counts),
        Counts ins 0..Courts,
        foldl(triangle, Rows, Vss, Dss, 0, _),
        append(Vss, Vs),
        global_cardinality(Vs, Pairs),
        maplist(breaks, Dss),
        labeling([ff], Vs).

triangle(Row, Vs, Ds, N0, N) :-
        length(Prefix, N0),
        append(Prefix, [-|Vs], Row),
        append(Prefix, Vs, Ds),
        N #= N0 + 1.

breaks([]).
breaks([P|Ps]) :- maplist(breaks_(P), Ps), breaks(Ps).

breaks_(P0, P) :- abs(P0-P) #> 1.

Sample query: 5 players on 2 courts:

?- time(tennis(5, 2, Rows)), maplist(writeln, Rows).
% 827,838 inferences, 0.257 CPU in 0.270 seconds (95% CPU, 3223518 Lips)
[-,1,3,5,7]
[1,-,5,7,9]
[3,5,-,9,1]
[5,7,9,-,3]
[7,9,1,3,-]

The specified task, 6 players on 2 courts, solved well within the time limit of 1 minute:

?- time(tennis(6, 2, Rows)),
   maplist(format("~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+\n"), Rows).
% 6,675,665 inferences, 0.970 CPU in 0.977 seconds (99% CPU, 6884940 Lips)
  -  1  3  5  7 10
  1  -  6  9 11  3
  3  6  - 11  9  1
  5  9 11  -  2  7
  7 11  9  2  -  5
 10  3  1  7  5  -

Further example: 7 players on 5 courts:

?- time(tennis(7, 5, Rows)),
   maplist(format("~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+\n"), Rows).
% 125,581,090 inferences, 17.476 CPU in 18.208 seconds (96% CPU, 7185927 Lips)
  -  1  3  5  7  9 11
  1  -  5  3 11 13  9
  3  5  -  9  1  7 13
  5  3  9  - 13 11  7
  7 11  1 13  -  5  3
  9 13  7 11  5  -  1
 11  9 13  7  3  1  -

Variant 2: Solution with SICStus Prolog

With the following additional definitions for compatibility, the same program also runs in SICStus Prolog:

:- use_module(library(lists)).
:- use_module(library(between)).

:- op(700, xfx, ins).

Vs ins D :- maplist(in_(D), Vs).

in_(D, V) :- V in D.

chain([], _).
chain([L|Ls], Pred) :-
        chain_(Ls, L, Pred).

chain_([], _, _).
chain_([L|Ls], Prev, Pred) :-
        call(Pred, Prev, L),
        chain_(Ls, L, Pred).

pairs_keys_values(Ps, Ks, Vs) :- keys_and_values(Ps, Ks, Vs).

foldl(Pred, Ls1, Ls2, Ls3, S0, S) :-
        foldl_(Ls1, Ls2, Ls3, Pred, S0, S).

foldl_([], [], [], _, S, S).
foldl_([L1|Ls1], [L2|Ls2], [L3|Ls3], Pred, S0, S) :-
        call(Pred, L1, L2, L3, S0, S1),
        foldl_(Ls1, Ls2, Ls3, Pred, S1, S).

time(Goal) :-
        statistics(runtime, [T0|_]),
        call(Goal),
        statistics(runtime, [T1|_]),
        T #= T1 - T0,
        format("% Runtime: ~Dms\n", [T]).

Major difference: SICStus, being a commercial-grade Prolog that ships with a serious CLP(FD) system, is much faster than SWI-Prolog in this use case and others like it.

The specified task, 6 players on 2 courts:

?-   time(tennis(6, 2, Rows)),
     maplist(format("~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+\n"), Rows).
% Runtime: 34ms (!)
  -  1  3  5  7 10
  1  -  6 11  9  3
  3  6  -  9 11  1
  5 11  9  -  2  7
  7  9 11  2  -  5
 10  3  1  7  5  -

The larger example:

| ?- time(tennis(7, 5, Rows)),
   maplist(format("~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+~t~w~3+\n"), Rows).
% Runtime: 884ms
  -  1  3  5  7  9 11
  1  -  5  3  9  7 13
  3  5  -  1 11 13  7
  5  3  1  - 13 11  9
  7  9 11 13  -  3  1
  9  7 13 11  3  -  5
 11 13  7  9  1  5  -

Closing remarks

In both systems, global_cardinality/3 allows you to specify options that alter the propagation strength of the global cardinality constraint, enabling weaker and potentially more efficient filtering. Choosing the right options for a specific example may have an even larger impact than the choice of Prolog system.

Leave a Comment