开发者

Tennis match scheduling

There are a limited number of players and a limited number of tennis courts. At each round, there can be at most as many matches as there are courts. Nobody plays 2 rounds without a break. Everyone plays a match against everyone else. Produce the schedule that takes as few rounds as possible. (Because of the rule that there must a break between rounds for everyone, there can be a round without matches.) The output for 5 pl开发者_Go百科ayers and 2 courts could be:

 |  1   2   3   4   5
-|------------------- 
2|  1   - 
3|  5   3   - 
4|  7   9   1   - 
5|  3   7   9   5   -

In this output the columns and rows are the player-numbers, and the numbers inside the matrix are the round numbers these two players compete.

The problem is to find an algorithm which can do this for larger instances in a feasible time. We were asked to do this in Prolog, but (pseudo-) code in any language would be useful.

My first try was a greedy algorithm, but that gives results with too many rounds. Then I suggested an iterative deepening depth-first search, which a friend of mine implemented, but that still took too much time on instances as small as 7 players.

(This is from an old exam question. No one I spoke to had any solution.)


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.


This is very similar to the Traveling Tournament Problem, which is about scheduling football teams. In TTP, they can find the optimal solution up to only 8 teams. Anyone who breaks an ongoing record of 10 or more teams, has it a lot easier to get published in a research journal.

It is NP hard and the trick is to use meta-heuristics, such as tabu search, simulated annealing, ... instead of brute force or branch and bound.

Take a look my implementation with Drools Planner (open source, java). Here are the constraints, it should be straightforward to replace that with constraints such as Nobody plays 2 rounds without a break.


Each player must play at least n - 1 matches where n is the number of players. So the minimum of rounds is 2(n - 1) - 1, since every player needs to rest a match. The minimum is also bound by (n(n-1))/2 total matches divided by number of courts. Using the smallest of these two gives you the length of the optimal solution. Then it's a matter of coming up with a good lower estimating formula ((number of matches+rests remaining)/courts) and run A* search.

As Geoffrey said, I believe the problem is NP Hard, but meta-heuristics such as A* is very applicable.


Python Solution:

import itertools

def subsets(items, count = None):
    if count is None:
        count = len(items)

    for idx in range(count + 1):
        for group in itertools.combinations(items, idx):
            yield frozenset(group)

def to_players(games):
    return [game[0] for game in games] + [game[1] for game in games]

def rounds(games, court_count):
    for round in subsets(games, court_count):
        players = to_players(round)
        if len(set(players)) == len(players):
            yield round

def is_canonical(player_count, games_played):
    played = [0] * player_count
    for players in games_played:
        for player in players:
            played[player] += 1

    return sorted(played) == played



def solve(court_count, player_count):
    courts = range(court_count)
    players = range(player_count)

    games = list( itertools.combinations(players, 2) )
    possible_rounds = list( rounds(games, court_count) )

    rounds_last = {}
    rounds_all = {}
    choices_last = {}
    choices_all = {}



    def update(target, choices, name, value, choice):
        try:
            current = target[name]
        except KeyError:
            target[name] = value
            choices[name] = choice
        else:
            if current > value:
                target[name] = value
                choices[name] = choice

    def solution(games_played, players, score, choice, last_players):
        games_played = frozenset(games_played)
        players = frozenset(players)

        choice = (choice, last_players)

        update(rounds_last.setdefault(games_played, {}), 
                choices_last.setdefault(games_played, {}), 
                players, score, choice)
        update(rounds_all, choices_all, games_played, score, choice)

    solution( [], [], 0, None, None)

    for games_played in subsets(games):
        if is_canonical(player_count, games_played):
            try:
                best = rounds_all[games_played]
            except KeyError:
                pass
            else:
                for next_round in possible_rounds:
                    next_games_played = games_played.union(next_round)

                    solution( 
                        next_games_played, to_players(next_round), best + 2,
                        next_round, [])

                for last_players, score in rounds_last[games_played].items():
                    for next_round in possible_rounds:
                        if not last_players.intersection( to_players(next_round) ):
                            next_games_played = games_played.union(next_round)
                            solution( next_games_played, to_players(next_round), score + 1,
                                    next_round, last_players)

    all_games = frozenset(games)


    print rounds_all[ all_games ]
    round, prev = choices_all[ frozenset(games) ]
    while all_games:
        print "X ", list(round)
        all_games = all_games - round
        if not all_games:
            break
        round, prev = choices_last[all_games][ frozenset(prev) ]

solve(2, 6)

Output:

11
X  [(1, 2), (0, 3)]
X  [(4, 5)]
X  [(1, 3), (0, 2)]
X  []
X  [(0, 5), (1, 4)]
X  [(2, 3)]
X  [(1, 5), (0, 4)]
X  []
X  [(2, 5), (3, 4)]
X  [(0, 1)]
X  [(2, 4), (3, 5)]

This means it will take 11 rounds. The list shows the games to be played in the rounds in reverse order. (Although I think the same schedule works forwards and backwords.) I'll come back and explain why I have the chance.

Gets incorrect answers for one court, five players.


Some thoughts, perhaps a solution...

Expanding the problem to X players and Y courts, I think we can safely say that when given the choice, we must select the players with the fewest completed matches, otherwise we run the risk of ending up with one player left who can only play every other week and we end up with many empty weeks in between. Picture the case with 20 players and 3 courts. We can see that during round 1 players 1-6 meet, then in round 2 players 7-12 meet, and in round 3 we could re-use players 1-6 leaving players 13-20 until later. Therefor, I think our solution cannot be greedy and must balance the players.

With that assumption, here is a first attempt at a solution:

 1. Create master-list of all matches ([12][13][14][15][16][23][24]...[45][56].)
 2. While (master-list > 0) {
 3.     Create sub-list containing only eligible players (eliminate all players who played the previous round.)
 4.     While (available-courts > 0) {
 5.         Select match from sub-list where player1.games_remaining plus player2.games_remaining is maximized.
 6.         Place selected match in next available court, and 
 7.         decrement available-courts.
 8.         Remove selected match from master-list.
 9.         Remove all matches that contain either player1 or player2 from sub-list.
10.     } Next available-court
11.     Print schedule for ++Round.
12. } Next master-list

I can't prove that this will produce a schedule with the fewest rounds, but it should be close. The step that may cause problems is #5 (select match that maximizes player's games remaining.) I can imagine that there might be a case where it's better to pick a match that almost maximizes 'games_remaining' in order to leave more options in the following round.

The output from this algorithm would look something like:

Round    Court1    Court2
  1       [12]      [34]
  2       [56]       --
  3       [13]      [24]
  4        --        --
  5       [15]      [26]
  6        --        --
  7       [35]      [46]
  .         .         .

Close inspection will show that in round 5, if the match on Court2 had been [23] then match [46] could have been played during round 6. That, however, doesn't guarantee that there won't be a similar issue in a later round.

I'm working on another solution, but that will have to wait for later.


I don't know if this matters, the "5 Players and 2 Courts" example data is missing three other matches: [1,3], [2,4] and [3,5]. Based on the instruction: "Everyone plays a match against everyone else."

0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜