module Exercise02 where import Data.List import Data.Ord import Data.Maybe import qualified Data.Set as Set(Set, singleton, fromList, isSubsetOf, union, unions, toList, map, fromList, empty) {-H2.1a)-} twoThirdsAverageWinners :: [(String, Int)] -> [String] twoThirdsAverageWinners gs = map fst $ takeWhile isLowest sortedList where twoThirds = ((2 * (sum . map snd $ gs)) `div` length gs) `div` 3 mapToDifference (s,i) = (s, abs $ twoThirds - i) sortedList = sortOn snd $ map mapToDifference gs isLowest (_, i) = snd (head sortedList) == i {-H2.1b)-} lowestUniqueBidder :: [(String, Int)] -> String lowestUniqueBidder bs = fst $ fromMaybe ("Nobody",1) . listToMaybe $ concat $ filter (\x -> length x == 1) $ groupBy secondEqual $ sortOn snd bs where secondEqual (_,b) (_,b2) = b == b2 {-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 = players tournament \\ (i:dominion tournament i) {-H2.2b)-} covers :: [[Int]] -> Int -> Int-> Bool covers tournament i j = subset (dominion tournament j) (dominion tournament i) subset :: (Foldable t1, Foldable t2, Eq a) => t1 a -> t2 a -> Bool subset xs ys = all (`elem` ys) xs {-2.2c)-} dominant :: [[Int]] -> [Int] -> Bool dominant _ [] = False dominant tournament xs = all beatEveryOther xs where beatEveryOther x = subset everyOther (dominion tournament x) everyOther = filter (`notElem` xs) (players tournament) {-WETT-} {-H2.2d)-} copeland :: [[Int]] -> [Int] copeland tournament = map snd . filter ((maximum lengths == ) . fst ) $ zip lengths $ enumFrom 1 where lengths = length <$> tournament {-H2.2e)-} uncoveredSet :: [[Int]] -> [Int] uncoveredSet tournament = filter (\player -> not . any (flip (covers tournament) player) $ delete player playerss) playerss where playerss = players tournament topCycle :: [[Int]] -> [Int] topCycle tournament = shortest $ Set.toList . until (extension Set.isSubsetOf) (extension Set.union) . Set.singleton <$> players tournament where extension f g = f (Set.unions $ Set.map (dominatorSets !! ) g) g dominatorSets = Set.empty: (Set.fromList . dominators tournament <$> players tournament) {-TTEW-} {-H2.2f)-} topCycle' :: [[Int]] -> [Int] topCycle' tournament = shortest . filter (dominant tournament) . tail . subsequences $ players tournament copeland' tournament = map fst . filter equalMax $ zip [1..] $ map length tournament where maxLength = maximum . map length $ tournament equalMax a = maxLength == snd a {-H2.2e)-} uncoveredSet' :: [[Int]] -> [Int] uncoveredSet' tournament = filter uncovered $ players tournament where uncovered::Int -> Bool uncovered player = not . any (\other -> covers tournament other player) $ delete player $ players tournament {-H2.2f)-} ex10 :: [[Int]] ex10 = [[2,3,4,5,6,8,9],[3,5,6],[5,8],[2,3,5,6,7,8,9,10],[],[3,5,8],[1,2,3,5,6,8,9],[2,5],[2,3,5,6,8],[1,2,3,5,6,7,8,9]] -- CO: [4, 10] -- UC: [1, 4, 10] -- TC: [1, 4, 7, 10] ex20 :: [[Int]] ex20 = [[2,3,4,5,6,7,8,9,10,11,12,13,15,16,18,19,20],[3,4,5,8,10,13,15,19],[4,5,12,13,15,19,20],[6,10,13,15,19],[4,9,10,13,15,19,20],[2,3,5,9,13,15,19],[2,3,4,5,6,8,9,10,11,12,13,15,19],[3,4,5,6,9,11,13,15,19],[2,3,4,10,11,13,15,19,20],[3,6,8,11,13,15,19],[2,3,4,5,6,13,15,19],[2,4,5,6,8,9,10,11,13,15,19],[19],[1,2,3,4,5,6,7,8,9,10,11,12,13,15,17,19,20],[13,19],[2,3,4,5,6,7,8,9,10,11,12,13,14,15,18,19,20],[1,2,3,4,5,6,7,8,9,10,11,12,13,15,16,18,19,20],[2,3,4,5,6,7,8,9,10,11,12,13,14,15,19,20],[],[2,4,6,7,8,10,11,12,13,15,19]] -- CO: [17] -- UC: [14,16,17] -- TC: [1,14,16,17,18] ex30 :: [[Int]] ex30 = [[2,3,5,6,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30],[18,23,29],[2,7,8,10,11,14,18,19,20,21,22,23,25,26,27,28,29],[1,2,3,6,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30],[2,3,4,6,7,8,9,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30],[2,3,7,8,10,11,13,14,15,17,18,19,20,22,23,24,25,26,27,28,29,30],[2,8,10,11,14,17,18,20,22,23,24,25,26,27,28,29],[2,10,11,14,18,19,20,23,25,26,27,28],[1,2,3,4,6,7,8,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30],[2,18,23,28],[2,10,18,23,28],[2,3,6,7,8,10,11,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29],[2,3,7,8,10,11,14,17,18,19,20,21,22,23,24,25,26,27,28,29,30],[2,10,11,18,19,20,23,25,26,27,28,29],[2,3,7,8,10,11,13,14,17,18,19,20,22,23,25,26,27,28,29],[1,2,3,4,5,6,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30],[2,3,8,10,11,14,18,19,20,23,25,26,27,28,29],[23],[2,7,10,11,18,23,25,28],[2,10,11,18,19,22,23,25,26,27,28,29],[2,6,7,8,10,11,14,15,17,18,19,20,22,23,24,25,26,27,28,29,30],[2,8,10,11,14,17,18,19,23,24,25,26,27,28,29,30],[],[2,3,8,10,11,14,15,17,18,19,20,23,25,26,27,28,29],[2,10,11,18,23,28],[2,10,11,18,19,23,25,27,28],[2,10,11,18,19,23,25,28],[2,18,23],[8,10,11,18,19,23,25,26,27,28],[2,3,7,8,10,11,12,14,15,17,18,19,20,23,24,25,26,27,28,29]] -- CO: [9,16] -- UC: [5,9,16] -- TC: [1,4,5,9,16] ex35 :: [[Int]] ex35 = [[2,3,4,5,6,7,9,12,13,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[3,4,5,6,7,9,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[4,5,6,12,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[5,6,12,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[29],[5,14,18,21,22,23,24,26,27,29,31,35],[3,4,5,6,9,12,14,18,19,20,21,22,23,24,25,26,27,29,30,31,35],[1,2,3,4,5,6,7,9,10,12,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[3,4,5,6,14,18,19,21,22,23,24,25,26,27,29,30,35],[1,2,3,4,5,6,7,9,11,12,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[1,2,3,4,5,6,7,8,9,12,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[2,5,6,9,13,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[2,3,4,5,6,7,8,9,10,11,14,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[5,18,27,35],[1,2,3,4,5,6,7,8,9,10,11,12,13,14,17,18,19,20,21,22,23,24,25,26,27,29,30,31,32,33,34,35],[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,29,30,31,33,34,35],[1,2,3,4,5,6,7,8,9,10,11,12,13,14,18,19,20,21,22,23,24,25,26,27,28,29,30,31,34,35],[5],[5,6,14,18,21,22,23,26,27,29,31,35],[5,6,9,14,18,19,21,23,26,27,29,30,31,34,35],[5,14,18,23,27,31],[5,14,18,20,21,23,27,29,30,31,35],[5,14,18,27,35],[5,14,18,19,20,21,22,23,27,29,31,35],[5,6,14,18,19,20,21,22,23,24,26,27,29,30,31,35],[5,14,18,21,22,23,24,27,29,30,31,34,35],[5,18,29,31],[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,18,19,20,21,22,23,24,25,26,27,29,30,31,34,35],[14,18,21,23],[5,6,14,18,19,21,23,24,27,29,31,35],[5,9,14,18,23,29],[1,2,3,4,5,6,7,8,9,10,11,12,13,14,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,34,35],[1,2,3,4,5,6,7,8,9,10,11,12,13,14,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,34,35],[5,6,7,9,14,18,19,21,22,23,24,25,27,29,30,31,35],[5,18,21,27,29,31]] -- CO: [15,16,32,33] -- UC: [15,16,28,32,33] -- TC: [15,16,17,28,32,33] ex50 :: [[Int]] ex50 = [[2,5,7,10,11,12,13,14,17,18,19,20,21,22,23,24,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,44,49,50],[5,7,8,10,11,12,14,15,17,18,19,20,21,22,23,24,26,27,29,30,31,32,33,35,36,37,38,39,41,42,43,44,48,49,50],[1,2,5,6,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,45,46,48,49,50],[1,2,3,5,6,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,45,48,49,50],[7,11,36,37],[1,2,5,7,8,9,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50],[26,36],[1,5,7,10,11,12,14,18,19,20,21,22,23,24,26,27,29,30,31,32,33,35,36,37,38,39,41,42,44,49,50],[1,2,3,4,5,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50],[5,7,11,12,14,18,21,22,24,26,27,29,30,31,32,33,35,36,37,39,41,42,44,49,50],[7,27,36],[5,7,11,18,21,22,24,26,27,29,30,33,35,36,37,39,42,50],[2,5,7,8,10,11,12,14,17,18,19,20,21,22,23,24,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,49,50],[5,7,11,12,18,21,22,24,26,27,29,30,31,32,33,35,36,37,39,42,44,49,50],[1,5,7,8,10,11,12,13,14,17,18,19,20,21,22,23,24,25,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,45,49,50],[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,45,46,47,48,49,50],[5,7,8,10,11,12,14,18,19,21,22,23,24,26,27,29,30,31,32,33,34,35,36,37,39,41,42,44,49,50],[5,7,11,22,24,26,27,29,30,32,33,36,37,39,42,44,50],[5,7,10,11,12,14,18,21,22,24,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,44,49,50],[5,7,10,11,12,14,17,18,19,21,22,24,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,44,49,50],[5,7,11,18,22,24,26,27,29,30,33,36,37,39,44],[5,7,11,27,29,36],[5,7,10,11,12,14,18,19,20,21,22,24,26,27,29,30,31,32,33,35,36,37,38,39,41,42,44,49,50],[5,7,11,22,26,27,29,33,36,39,42,50],[1,2,5,7,8,10,11,12,13,14,17,18,19,20,21,22,23,24,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,48,49,50],[5,11,22,29,33,36,39],[5,7,26,29,33,36,37,44],[1,2,5,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,45,48,49,50],[5,7,11,36,42],[5,7,11,22,24,26,27,29,33,36],[5,7,11,12,18,21,22,24,26,27,29,30,32,33,35,36,37,38,39,41,42,44,49,50],[5,7,11,12,21,22,24,26,27,29,30,33,35,36,37,39,41,42,44,50],[5,7,11,22,29,36],[2,5,7,8,10,11,12,14,18,21,22,23,24,26,27,29,30,31,32,33,35,36,37,38,39,41,42,44,49,50],[5,7,11,18,21,22,24,26,27,29,30,33,36,37,39,41,42,44,50],[],[7,11,22,24,26,29,30,33,36,42],[5,7,10,11,12,14,17,18,21,22,24,26,27,29,30,32,33,35,36,37,39,41,42,44,49,50],[5,7,11,22,27,29,30,33,36,37],[1,2,3,4,5,7,8,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,45,47,48,49,50],[5,7,11,12,14,18,21,22,24,26,27,29,30,33,36,37,39,42,44,49],[5,7,11,21,22,26,27,30,33,36,39],[1,5,7,8,10,11,12,14,17,18,19,20,21,22,23,24,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,44,48,49,50],[5,7,11,12,22,24,26,29,30,33,36,37,39,42,49],[1,2,5,7,8,10,11,12,13,14,17,18,19,20,21,22,23,24,25,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,48,49,50],[1,2,4,5,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,47,48,49,50],[1,2,3,4,5,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,41,42,43,44,45,48,49,50],[1,5,7,8,10,11,12,13,14,15,17,18,19,20,21,22,23,24,26,27,29,30,31,32,33,34,35,36,37,38,39,41,42,44,49,50],[5,7,11,12,18,21,22,24,26,27,29,30,32,33,35,36,37,39,42,50],[5,7,11,21,22,26,27,29,30,33,36,37,39,41,42,44]] -- CO: [16] -- UC: [6,9,16,40] -- TC: [3,4,6,9,16,40,46,47]