I am trying to make a scheduling program of a football tournament,
- There are 6 groups with 5 teams each
- Each team will play 4 games, 2 home 2 away match
- there are no more than three matches on any day
- each team has at least 4 rest days between matches.
Here is my code, create_schedule([H|T], NewRestTeams, N, RestGames)
starts from day N
to day 30. RestGames
are possible remaining games, and NewRestTeams
are resting teams after a game.
It works just fine until N
is 18. But after decreasing the N
i don't get any result.
:- use_module(library(clpfd)).
% teams
team([a1,b1,c1,d1,e1]).
team([a2,b2,c2,d2,e2]).
team([a3,b3,c3,d3,e3]).
team([a4,b4,c4,d4,e4]).
team([a5,b5,c5,d5,e5]).
team([a6,b6,c6,d6,e6]).
% A sample matching
gamessss(X):-X =
[a1-b1, a1-c1, d1-a1, e1-a1, b1-c1, b1-d1, e1-b1, c1-d1, c1-e1, d1-e1,
a2-b2, a2-c2, d2-a2, e2-a2, b2-c2, b2-d2, e2-b2, c2-d2, c2-e2, d2-e2,
a3-b3, a3-c3, d3-a3, e3-a3, b3-c3, b3-d3, e3-b3, c3-d3, c3-e3, d3-e3,
a4-b4, a4-c4, d4-a4, e4-a4, b4-c4, b4-d4, e4-b4, c4-d4, c4-e4, d4-e4,
a5-b5, a5-c5, d5-a5, e5-a5, b5-c5, b5-d5, e5-b5, c5-d5, c5-e5, d5-e5,
a6-b6, a6-c6, d6-a6, e6-a6, b6-c6, b6-d6, e6-b6, c6-d6, c6-e6, d6-e6].
matches(X) :-
team(Teams),
append(_, [A|T], Teams),
member(B, T),
( X = A-B
; X = B-A
).
%finds all possible games of the teams.
% all_games(Xs):- bagof(X, matches(X), Xs).
%creates possible matches for a day
create_matche_day(List,Xs, RestList) :-
member(X-Y,Xs) , %match1
member(Z-T,Xs), %match2
member(U-B,Xs), %match3
not(member([_,X],RestList)),
not(member([_,Y],RestList)),
not(member([_,Z],RestList)),
not(member([_,T],RestList)),
not(member([_,U],RestList)),
not(member([_,B],RestList)),
not(X=Y),
not(X=Z),
not(X=T),
not(X=U),
not(X=B),
not(Y=Z),
not(Y=T),
not(Y=U),
not(Y=B),
not(Z=T),
not(Z=U),
not(Z=B),
not(T=U),
not(T=B),
not(U=B),
List = [X-Y,Z-T,U-B] .
% deletes played matches from all possible games list
new_delete([],_,[]).
new_delete([K|T], [U,K,L],Ts):-new_delete(T, [U,K,L] ,Ts ), !.
new_delete([U|T], [U,K,L],Ts):-new_delete(T, [U,K,L] ,Ts ), !.
new_delete([L|T], [U,K,L],Ts):-new_delete(T, [U,K,L] ,Ts ), !.
new_delete([H|T],[U,K,L],[H|Ts]):-not(H=T) , not(H=K) , not(H=L),new_delete(T,[U,K,L],Ts),!.
% add the team which played a game to resting list
add_resteams([],[X-Y,Z-T,U-B],[[4,X],[4,Y],[4,Z],[4,T],[4,U],[4,B]]).
add_resteams([H|T],X,[H|L]):-add_resteams(T,X,L).
%Decrease the resting teams rest of the days and if it is zero remove the team from resting team list
remove_from_resteams([], []):- !.
remove_from_resteams([[A,_]|T], Temp):- X is A-1, X = 0, remove_from_resteams(T, Temp),!.
remove_from_resteams([[A,B]|T], [[X,B]|U]):- X is A-1, not(X = 0), remove_from_resteams(T, U),!.
day(_,_).
%create_schedule(dayList, RestingTeams,DayNumber,AllGames)
create_schedule([],[],30, T):-gamessss(T), !.
create_schedule([H|T], NewRestTeams, N, RestGames):-
X is N+1,
create_schedule(T, OldOldRestTeam, X, AllGames) ,
remove_from_resteams(OldOldRestTeam,OldRestTeam),
create_matche_day([U,K,L],AllGames, OldRestTeam),
add_resteams(OldRestTeam, [U,K,L],NewRestTeams),
H = day(X, [U,K,L]),
new_delete(AllGames, [U,K,L], RestGames).
Here the result of create_schedule(Possible, _, 18, _).
PossibleGames = [day(19, [e5-b5, d6-a6, b6-c6]), day(20, [d4-a4, b4-c4, d5-a5]), day(21, [e2-b2, d3-a3, b3-c3]), day(22, [d1-a1, b1-c1, d2-a2]), day(23, [b5-c5, a6-c6, b6-d6]), day(24, [a4-c4, b4-d4, e5-a5]), day(25, [b2-c2, a3-c3, b3-d3]), day(26, [a1-c1, b1-d1, e2-a2]), day(27, [c5-d5, a6-b6, c6-d6]), day(28, [a4-b4, c4-d4, a5-b5]), day(29, [c2-d2, a3-b3, c3-d3]), day(30, [a1-b1, c1-d1, a2-b2])],
RestingTeams = [[1, e2], [1, b2], [1, d3], [1, a3], [1, b3], [1, c3], [2, d4], [2, a4], [2, b4], [2, c4], [2, d5], [2, a5], [3, e5], [3, b5], [3, d6], [3, a6], [3, b6], [3, c6]]
My questions are:
Why my program does not work if
N
is less than 18 ?,How can I produce 2 home-2 away totally 4 matches for a team ?
I can produce of all pairings of a group.