module Exc02 where -- import qualified List -- only needed for testing the results -- Some useful Haskell Prelude functions: -- concat :: MonadPlus m => [m a] -> m a -- drop :: Int -> [a] -> [a] -- elem :: Eq a => a -> [a] -> Bool -- even :: Integral a => a -> Bool -- filter :: (a -> Bool) -> [a] -> [a] -- flip :: (a -> b -> c) -> (b -> a -> c) -- length :: [a] -> Int -- map :: (a -> b) -> [a] -> [b] -- mod :: Integral a => a -> a -> a -- reverse :: [a] -> [a] -- take :: Int -> [a] -> [a] import Types import List import qualified Complex -- just for testing -- P-8 fact :: (Integral a) => a -> a fact 0 = 1 fact n = n*(fact (n-1)) over :: (Integral a) => a -> a -> a over n k = fromIntegral (fact n) `div` (fromIntegral ((fact k)*(fact (n-k)))) -- exponentiation of complex numbers comp_exp :: (Integral a) => Complex3 a -> a -> Complex3 a -- more general: comp_exp :: (Integral a, Integral b) => Complex3 a -> b -> Complex3 a comp_exp (a:+b) n = sum [ over n i * a^(n-i) * (-1)^(i `div` 2) * (b^i) | i <- [0..n], even i ] :+ sum [ over n i * a^(n-i) * (-1)^((i-1) `div` 2) * (b^i) | i <- [0..n], odd i ] -- TESTME: -- # comp_exp (2:+3) 2 -- (-5) :+ 12 -- compare this with using the Complex library and pre-defined exponentiation -- # (2 Complex.:+ 3)^2 -- (-5.0) :+ 12.0 -- P-2 -- sieve of Erathostenes sieve :: [Integer] sieve = sieve' [2..] where sieve' (x:xs) = x:(sieve' . filter (\n -> n `mod` x /= 0) $ xs) -- P-3 -- tree def and showTree from Exc01 data NTree a = Branch a [NTree a] deriving (Eq) -- build a binary tree; just for testing mkTree :: [a] -> NTree a mkTree [] = error "mkTree: empty input list" mkTree [x] = Branch x [] mkTree [x,y] = Branch x [Branch y []] mkTree (x:xs) = Branch x [left, right] where (l,r) = halve xs left = mkTree l right = mkTree r halve xs = splitAt (length xs `div` 2) xs showTree :: (Eq a, Show a) => NTree a -> String showTree (Branch x []) = show x showTree (Branch x xs) = show x ++ "(" ++ List.concat (List.intersperse "," (map showTree xs)) ++ ")" -- uses a binary function foldTree :: (a -> a -> a) -> NTree a -> a foldTree f (Branch x xs) = foldl f x (map (foldTree f) xs) -- uses a function of 'Branch' type foldTree' :: (a -> [a] -> a) -> NTree a -> a foldTree' f (Branch x xs) = f x (map (foldTree' f) xs) -- unused flatten :: NTree a -> [a] flatten (Branch x xs) = x:(concat . map flatten $ xs) flatten' :: (Show a) => NTree a -> String flatten' (Branch x xs) = show x ++ "(" ++ (concat . map flatten' $ xs) ++ ")" -- H-1: see cesar-cipher-exc.hs