-- University of Zagreb -- Faculty of Electrical Engineering and Computing -- -- PROGRAMMING IN HASKELL -- -- Academic Year 2013/2014 -- The following are some *example* solutions to the 7th homework -- assignment. You were not required to write them out exactly like -- this. If you spot an error somewhere, please notify us. Thanks! module Homework where import Data.Maybe (mapMaybe) -- 1 data Date = Date { day :: Int, month :: Int, year :: Int } data Animal = Animal { species :: String, name :: String, legNum :: Maybe Int, birthday :: Date, dangerLvl :: Int } testDog :: Animal testDog = Animal "Dog" "Fluffy" (Just 4) (Date 16 3 1975) 10 -- 1a avgLegNum :: [Animal] -> Double avgLegNum = mean . map fromIntegral . mapMaybe legNum mean :: Fractional a => [a] -> a mean = uncurry (/) . foldr suminc (0, 0) where suminc x (s, n) = (s+x, n+1) -- 1b canDrinkBeer :: [Animal] -> [String] canDrinkBeer = map name . filter adult where adult = (>=18) . (2014-) . year . birthday -- 1c getFakeId :: Int -> Animal -> Animal getFakeId diff a = a { birthday = (birthday a) { year = born + diff }} where born = year $ birthday a -- This exercise shows us how cumbersome Haskell's record syntax can -- be when we want to modify a field deeply-nested within multiple -- layers of data structures. This is one of the reasons why many -- Haskellers dislike the record syntax and wish it to be changed. -- -- One way to bypass Haskell's record syntax is by using lenses. They -- make it possible to modify structures using ordinary functions, and -- without having to repeat yourself when modifying a deeply-nested -- field. For example, using the `lens` package, we could rewrite -- getFakeId like this: -- -- > getFakeId :: Int -> Animal -> Animal -- > getFakeId diff = over (birthday.year) (+diff) -- -- You can read more about what lenses are, how they are useful and -- how to use them here: -- http://stackoverflow.com/questions/10788261/what-are-lenses-used-useful-for -- https://www.fpcomplete.com/school/to-infinity-and-beyond/pick-of-the-week/basic-lensing -- https://www.fpcomplete.com/school/to-infinity-and-beyond/pick-of-the-week/a-little-lens-starter-tutorial -- 2 data BinaryTree a = Null | Node a (BinaryTree a) (BinaryTree a) testTree :: BinaryTree Int testTree = Node 1 (Node 2 (Node (-4) Null Null) (Node 3 Null Null)) (Node 2 (Node 1 Null (Node 10 Null (Node (-2) Null Null))) Null) -- 2a numNodes :: BinaryTree a -> Int numNodes Null = 0 numNodes (Node _ l r) = 1 + numNodes l + numNodes r -- 2b averageNodeDegree :: BinaryTree a -> Double averageNodeDegree Null = 0 averageNodeDegree tree = uncurry (/) $ count tree (0, 0) where count (Node _ Null Null) (c, n) = (c, n+1) count (Node _ Null r ) (c, n) = count r (c+1, n+1) count (Node _ l Null) (c, n) = count l (c+1, n+1) count (Node _ l r ) (c, n) = count r $ count l (c+2, n+1) -- 2c treeDepth :: BinaryTree a -> Int treeDepth Null = 0 treeDepth tree = depth tree 0 where depth Null d = d depth (Node _ l r) d = depth l (d+1) `max` depth r (d+1) -- 2d preorder :: BinaryTree a -> [a] preorder Null = [] preorder (Node x l r) = x : preorder l ++ preorder r -- 2e inorder :: BinaryTree a -> [a] inorder Null = [] inorder (Node x l r) = inorder l ++ x : inorder r -- 2f postorder :: BinaryTree a -> [a] postorder Null = [] postorder (Node x l r) = postorder l ++ postorder r ++ [x] -- 3a type Limit = Int data BList a = BList { contents :: [a], count :: Int, limit :: Limit } -- 3b empty :: Limit -> BList a empty = BList [] 0 -- 3c fromList :: [a] -> BList a fromList xs = let l = length xs in BList xs l l -- 3d limited :: Limit -> BList a -> BList a limited l (BList xs c _) = BList (take l xs) (min c l) l -- 3e cons :: a -> BList a -> BList a cons x (BList xs c lim) | c+1 > lim = error "too many elements!" | otherwise = BList (x:xs) (c+1) lim -- 3f concat' :: [BList a] -> BList a concat' bs = BList (concatMap contents bs) (sum $ map count bs) (sum $ map limit bs) -- 4 -- TODO -- 5 -- TODO