module Exercise02 where import Data.List import Data.Ord import Data.Maybe import Data.Function import Data.Bool {-H2.1a)-} twoThirdsAverageWinners :: [(String, Int)] -> [String] twoThirdsAverageWinners gs = map fst (filter (\i -> snd i == min) l) where min = minimum (map snd l) l = map (\x -> (fst x, abs(snd x - z))) gs z = floor (2*a / 3) a = fromIntegral (sum (map snd gs)) / genericLength gs {-H2.1b)-} lowestUniqueBidder :: [(String, Int)] -> String lowestUniqueBidder bs = if null us then "Nobody" else fst (head name) where name = filter (\s -> snd s == min) bs us = concat(filter(\s -> length s == 1) (groupBy (\x y -> snd x == snd y) (sortOn snd bs))) min = minimum(map snd us) {-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 = map (+1) (findIndices(\x -> i `elem` x) tournament) {-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 tournament xs = not (null xs) && all(\x -> y `isSubsequenceOf` dominion tournament x) xs where y = players tournament \\ xs {-WETT-} {-H2.2d)-} copeland :: [[Int]] -> [Int] copeland tournament = succ <$> maximum (fmap length tournament) `elemIndices` fmap length tournament -- fmap $ (elemIndices $ succ <$> . maximum x) x where x = fmap length tournament -- copeland tournament = succ <$> maximum (fmap length tournament) `elemIndices` fmap length tournament -- copeland tournament = let y = fmap length tournament in succ <$> maximum y `elemIndices` y -- copeland tournament = succ <$> foldl1' max xs `elemIndices` xs where xs = length <$> tournament -- copeland tournament = succ <$> maximum (length `map` tournament) `elemIndices` (length <$> tournament) -- copeland tournament = succ <$> length (comparing length `maximumBy` tournament) `elemIndices` (length `map` tournament) -- copeland tournament = map succ $ elemIndices(length $ comparing length `maximumBy` tournament) $ length `map` tournament -- copeland tournament = map succ $ elemIndices(length $ comparing length `maximumBy` tournament) $ fmap length tournament -- copeland tournament = succ <$> elemIndices(length $ comparing length `maximumBy` tournament) (length <$> tournament) -- copeland tournament = succ <$> elemIndices(length (maximumBy (comparing length) tournament)) (fmap length tournament) -- copeland tournament = succ <$> findIndices(\x -> length x == length (maximumBy (comparing length) tournament)) tournament {-H2.2e)-} uncoveredSet :: [[Int]] -> [Int] uncoveredSet tournament = (\x -> null [ y | y <- x `delete` players tournament, covers tournament y x]) `filter` players tournament -- uncoveredSet tournament = (\x -> null [ y | y <- x `delete` players tournament, covers tournament y x]) `filter` players tournament -- uncoveredSet tournament = filter(\x -> null [ y | y <- delete x $ players tournament, covers tournament y x]) $ players tournament -- [ x | x <- players tournament, null [ y | y <- players tournament, y /= x && covers tournament y x]] -- uncoveredSet tournament = succ <$> findIndices(\x -> null [ y | y <- players tournament, y /= x && covers tournament y x]) (players tournament) {-H2.2f)-} topCycle :: [[Int]] -> [Int] topCycle tournament = helper $ uncoveredSet tournament where helper ls = bool(helper $ nub $ ls >>= dominators tournament) ls $ dominant tournament ls -- where helper ls = bool (helper $ nub $ ls >>= dominators tournament) ls $ dominant tournament ls -- where helper ls = bool (helper $ union ls $ ls >>= dominators tournament) ls $ dominant tournament ls -- where helper ls = if dominant tournament ls then ls else helper $ union ls $ ls >>= dominators tournament -- where helper ls = if dominant tournament ls then ls else helper $ ls `union` (dominators tournament `concatMap` ls) -- where helper ls = if dominant tournament ls then ls else helper $ ls `union` concatMap (dominators tournament) ls {-TTEW-}