Skip to content

Instantly share code, notes, and snippets.

@tkuriyama
Last active September 10, 2020 02:18
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save tkuriyama/53a8f622fca218c6a2d86e3a43de88cb to your computer and use it in GitHub Desktop.
Save tkuriyama/53a8f622fca218c6a2d86e3a43de88cb to your computer and use it in GitHub Desktop.
CIS 194 HW8
-- {-# OPTIONS_GHC -fno-warn-orphans #-}
module Party where
import Data.Semigroup
import Data.Tree
import Data.Function (on)
import Data.List (sortBy)
import Employee
-- Ex 1 - 4 (ex 2 skipped)
instance Semigroup GuestList where
(<>) (GL e1 s1) (GL e2 s2) = GL (e1 ++ e2) (s1 + s2)
instance Monoid GuestList where
mempty = GL [] 0
glCons :: Employee -> GuestList -> GuestList
glCons e@(Emp _ s) (GL es ss) = GL (e:es) (s + ss)
moreFun :: GuestList -> GuestList -> GuestList
moreFun g1 g2 = if g1 > g2 then g1 else g2
treeFold :: (a -> [b] -> b) -> b -> Tree a -> b
treeFold f i (Node {rootLabel = r, subForest = s})
= f r (map (treeFold f i) s)
nextLevel :: Employee -> [(GuestList, GuestList)] -> (GuestList, GuestList)
nextLevel e@(Emp _ s) [] = (GL [e] s, mempty)
nextLevel e xs = let right = map snd xs
best = map (uncurry moreFun) xs
in (glCons e $ mconcat right, mconcat best)
maxFun :: Tree Employee -> GuestList
maxFun t = uncurry moreFun $ treeFold nextLevel (mempty, mempty) t
-- Ex 5
sorted :: [Name] -> [Name]
sorted = sortBy (compare `on` (\n -> head $ words n))
readTree :: String -> Tree Employee
readTree = read
format :: GuestList -> String
format (GL es s) = "Total fun: " ++ show s ++ "\n" ++
(unlines . sorted $ map empName es)
main :: IO ()
main = do
content <- readFile "Company.txt"
let output = format . maxFun . readTree $ content
putStrLn $ output
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment