-- University of Zagreb -- Faculty of Electrical Engineering and Computing -- -- PROGRAMMING IN HASKELL -- -- Academic Year 2013/2014 -- The following are some *example* solutions to the 6th 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.List (foldl', sortBy) import Data.Ord (comparing) -- 1a fprime :: Integral a => a -> Bool fprime n = n <= 3 || foldr f True [2..n-1] where f i pprime = n `mod` i /= 0 && pprime -- 1b lprime :: Integral a => a -> Bool lprime n = n <= 3 || all ((/=0).(n `mod`)) [2..n-1] -- 1c rprime :: Integral a => a -> Bool rprime n = recurse $ n-1 where recurse i = i <= 3 || n `mod` i /= 0 && recurse (i-1) -- 2 cycle' :: [a] -> [a] cycle' [] = error "empty list" cycle' xs = let ys = foldr (:) ys xs in ys -- 3 mapMasked :: (a -> Int) -> [a -> b] -> [a] -> [b] mapMasked ifunc fs = map $ \x -> fs !! ifunc x $ x -- 4, but suffers from space leak mean :: Fractional a => [a] -> a mean = uncurry (/) . foldr suminc (0, 0) where suminc x (s, n) = (s+x, n+1) -- 4, better done with foldl and forcing strictness mean' :: Fractional a => [a] -> a mean' = uncurry (/) . foldl' suminc (0, 0) where suminc (s, n) x = seq s $ seq n (s+x, n+1) -- 5a ncomp :: [a -> a] -> a -> a ncomp = foldr (.) id -- 5b fsort :: (Fractional a, Ord a) => [a -> a] -> [a] -> [a -> a] fsort fs xs = sortBy (comparing $ mean' . flip map xs) fs -- 5c compsort :: (Fractional a, Ord a) => [a -> a] -> [a] -> a -> a compsort fs = ncomp . fsort fs -- 6 type Set a = a -> Bool -- 6a empty :: Set a empty = const False -- 6b single :: Eq a => a -> Set a single = (==) -- 6c union' :: Set a -> Set a -> Set a union' x y e = x e || y e -- 6d difference :: Set a -> Set a -> Set a difference x y e = x e && not (y e) -- 6e insert' :: Eq a => a -> Set a -> Set a insert' = union' . single -- 6f remove :: Eq a => a -> Set a -> Set a remove n x e = n /= e && x e -- 7 reduce :: [[a]] -> (a -> a -> a) -> (a -> a -> a) -> a reduce [] _ _ = error "List must not be empty - don't know what to return" reduce xs f g = foldr1 f $ map (foldr1 g) xs -- 8 -- TODO