module Exercise02 where import Data.List import Data.Ord {-H2.1a)-} twoThirdsAverageWinners :: [(String, Int)] -> [String] twoThirdsAverageWinners gs = map fst $ head . groupBy (\(_, a) (_, b) -> a == b) $ sortOn snd [(name, abs $ avg - g) | (name, g) <- gs] where avg = sum [snd a | a <- gs] * 2 `div` (3 * length gs) {-H2.1b)-} lowestUniqueBidder :: [(String, Int)] -> String lowestUniqueBidder bs = fst $ head (concat (filter (\g -> length g == 1) . groupBy (\(_, a) (_, b) -> a == b) $ sortOn snd bs) ++ [("Nobody", -1)]) {-H2-} -- returns the shortest list in a list of lists shortest :: [[Int]] -> [Int] shortest = minimumBy (comparing length) -- returns the set of all players in a tournament players :: [[Int]] -> [Int] players tournament = [1 .. length tournament] -- returns the dominion of player i dominion :: [[Int]] -> Int -> [Int] dominion tournament i = tournament !! (i - 1) {-H2.2a)-} dominators :: [[Int]] -> Int -> [Int] dominators tournament i = [j | j <- players tournament, i `elem` dominion tournament j] {-H2.2b)-} covers :: [[Int]] -> Int -> Int -> Bool covers tournament i j = null (dominion tournament j \\ dominion tournament i) {-2.2c)-} dominant :: [[Int]] -> [Int] -> Bool dominant _ [] = False dominant tournament xs = all null ([nxs \\ dominion tournament x | x <- xs]) where nxs = players tournament \\ xs {-WETT-} {-H2.2d)-} copeland :: [[Int]] -> [Int] copeland tournament = map succ $ elemIndices (maximum doms) doms where doms = map (length . dominion tournament) $ players tournament {-H2.2e)-} uncoveredSet :: [[Int]] -> [Int] uncoveredSet tournament = filter (\x -> not $ or [covers tournament y x | y <- delete x $ players tournament]) $ players tournament {-H2.2f)-} topCycle :: [[Int]] -> [Int] topCycle tournament = head . filter (dominant tournament) $ inits $ sortOn (Down . length . dominion tournament) $ players tournament -- naive approach -- topCycle :: [[Int]] -> [Int] -- topCycle tournament = shortest . filter (dominant tournament) $ subsequences $ players tournament {-TTEW-}