
% nhlDraftLottery(Teams)
% ----------------------
% given the order in which non-playoff teams finished the season,
%    ordered from worst to best, use the nhl draft lottery odds
%    to simulate a lottery draw for the first, second, and third
%    picks, displaying which teams win those three slots,
%    then print the complete draft order for the non-playoff teams
% e.g.
%    nhlDraftLottery([Col(Ott), Det, LA, NJ, Ana, Van, NYR, Buf,
%                     Edm, Chi, Col, Min, Fla, Phi, Mtl]).
nhlDraftLottery(Teams) :-
   Odds = [185, 135, 115, 95, 85, 75, 65, 60, 50, 35, 30, 25, 20, 15, 10],
   formTmList(Teams, Odds, TList1),
   drawPrize(TList1, Winner1), delete(TList1, [Winner1|_], TList2), delete(Teams, Winner1, Tms2),
   drawPrize(TList2, Winner2), delete(TList2, [Winner2|_], TList3), delete(Tms2, Winner2, Tms3),
   drawPrize(TList3, Winner3), delete(TList3, [Winner3|_], _), delete(Tms3, Winner3, Tms4), !,
   format("Drafting in first position: ~w~n", [Winner1]),
   format("Drafting in second position: ~w~n", [Winner2]),
   format("Drafting in third position: ~w~n", [Winner3]),
   printTheRest(Tms4, 4).


% printTheRest(Teams, CurPosition)
% --------------------------------
% prints each element of the list and its position
printTheRest([], _).
printTheRest([Tm|Rest], Pos) :- Next is Pos + 1,
   format("~w: ~w~n", [Pos,Tm]), printTheRest(Rest,Next).


% formTmList(Teams, Odds, Result)
% -------------------------------
% given a list of teams and a list of odds, pair them up to form result,
%    e.g. [X,Y,Z] and [10,20,30] => [X,10], [Y,20], [Z,30]
formTmList([], [], []).
formTmList([Tm|TRest], [Odds|ORest], [[Tm,Odds]|Result]) :- formTmList(TRest, ORest, Result).


% drawPrize(Contestants, Winner)
% ------------------------------
% given the list of contestants (each a [Name,NumTickets] pair)
%    simulate one draw, returning the name of the winner
% e.g.
%   drawPrize([[Bart,20], [Lisa, 10], [Maggie, 3], [Marge,7], [Homer, 4]], W).

% base cases: no contestants
drawPrize([], "none").

% general case, first contestant is winner so far, use pickAWinner for the real work
drawPrize([[Tm, Tix] | Rest ], W) :- pickAWinner(Rest, Tm, Tix, W).


% pickAWinner(Contestants, WinSoFar, TixSoFar, Winner)
% ----------------------------------------------------
% given the list of contestants still to check, the
%    winner so far and the number of tickets so far,
%    determine the overall winner

% base case: no contestants left, the winner so far is the overall winner
pickAWinner([], Winner, _, Winner).

% new winner case: next contestant replaces winner so far
pickAWinner([[Tm,Tix]|Rest], _, TixSoFar, Winner) :-
   TotalTix is Tix + TixSoFar, random(1,TotalTix,Draw), Draw =< Tix,
   pickAWinner(Rest, Tm, TotalTix, Winner).

% general case: next contestant does NOT replace winner so far
pickAWinner([[_|Tix]|Rest], WinnerSoFar, TixSoFar, Winner) :-
   TotalTix is Tix + TixSoFar, pickAWinner(Rest, WinnerSoFar, TotalTix, Winner).

% --------------------------------------------------------------------------------------------
%       Test cases
% --------------------------------------------------------------------------------------------

nhlTest(1) :- nhlDraftLottery(["Col(Ott)", "Det", "LA", "NJ", "Ana", "Van", "NYR", "Buf",
                               "Edm", "Chi", "Col", "Min", "Fla", "Phi", "Mtl"]).

