summaryrefslogtreecommitdiff
path: root/lec08/Party.hs
blob: bc2150e8c39f10453c28f5485cc2aacdf0abe4ca (plain)
1
2
3
4
5
6
7
8
9
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
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
module Party where

import Employee
import Data.Tree
import Data.List

-- Exercise 1

glCons :: Employee -> GuestList -> GuestList
glCons e@Emp { empFun = ef } (GL es cf) = GL (e:es) (cf + ef)

-- mappend (a.k.a. (<>)) has been moved to Semigroup
instance Semigroup GuestList where
  (<>) (GL es1 f1) (GL es2 f2) = GL (es1 ++ es2) (f1 + f2)

instance Monoid GuestList where
  mempty = GL [] 0

moreFun :: GuestList -> GuestList -> GuestList
moreFun gl1@(GL _ f1) gl2@(GL _ f2)
  | f1 >= f2  = gl1
  | otherwise = gl2

-- Exercise 2

treeFold :: (a -> [b] -> b) -> Tree a -> b
treeFold f (Node l subs) = f l $ map (\t -> treeFold f t) subs

-- Exercise 3

-- This exercise has been more troublesome than many others I've done, so here's
-- an explanation (for both myself and other readers).
--
-- We know that:
-- - We want to maximize the fun.
-- - All guests in a list have their fun added.
-- - Inviting a boss automatically sets the fun to zero for all the invited
--   employees immediately under that boss.
-- - As a consequence, if we recursively invite all bosses at all levels of the
--   company hierarchy, regardless of which other employees we also invite, then
--   only the CEO is going to have fun.
--
-- One way of maximizing the fun is to only invite employees who are not bosses
-- (the leaves in the tree of the company hierarchy) so that the fewest people
-- are excluded and we get most people's fun. However, a sub-boss could have
-- more fun than all of their immediate employees, which makes that sub-boss
-- more suitable to be invited, unless that sub-boss also have the fun set to
-- zero due to a boss immediately above being invited, in which case both the
-- sub-boss and all their employees are going to have no fun at all.
--
-- What this function is supposed to do here is, given a boss and a list of
-- guest list pairs for each level (whose first element includes the boss of
-- that level while the second does not), to compute an output pair whose first
-- element has the best guest list with the given boss while the second has the
-- best guest list without the given boss.
--
-- This implementation of the function calculates the two values for the output
-- pair as follows. Since we can't invite any sub-boss when we invite a boss,
-- then the most obvious answer for the first element is to just invite the
-- given boss and all lists with no bosses, which are the second of each pair.
-- As for the second element, since we don't invite the current boss, we're free
-- to choose whether or not to invite any sub-boss, which results in choosing
-- the list that most maximizes the fun in each pair.
--
-- Thanks you, Giacomo Cavalieri, for helping me write the solution!
nextLevel :: Employee -> [(GuestList, GuestList)] -> (GuestList, GuestList)
nextLevel boss outcomes = (bestWith, bestWithout)
  where
    bestWith    = glCons boss $ mconcat $ map snd outcomes
    bestWithout = mconcat $ map (uncurry max) outcomes

-- Exercise 4

maxFun :: Tree Employee -> GuestList
maxFun hierarchy = maximum $ treeFold nextLevel hierarchy

-- Exercise 5

glBare :: GuestList -> [Employee]
glBare (GL empList _) = empList

glFun :: GuestList -> Fun
glFun (GL _ fun) = fun

readEmpTree :: String -> Tree Employee
readEmpTree = read

names :: GuestList -> [String]
names = map empName . sortOn empName . glBare

printNames :: [String] -> IO ()
printNames = foldl1' (>>) . map putStrLn

printTotal :: GuestList -> IO ()
printTotal gl = putStrLn $ "Total fun: " ++ show (glFun gl)

printAll :: GuestList -> IO ()
printAll gl = printTotal gl >> printNames (names gl)

main :: IO ()
main = readFile "company.txt" >>= printAll . maxFun . readEmpTree