module Sol_Exercise_5 where import Test.QuickCheck import Data.List import Data.Maybe {- G1 -} {- Berechnet "gg (xx, yy)". -} {- G2 -} iter :: Int -> (a -> a) -> a -> a iter n f x | n <= 0 = x | otherwise = iter (n - 1) f (f x) pow :: Int -> Int -> Int pow n k = iter k mul 1 where mul x = n * x drop' :: Int -> [a] -> [a] drop' n xs = iter n tail xs replicate' :: Int -> a -> [a] replicate' n x = iter n cons [] where cons xs = x : xs {- G3 -} -- rekursiv partition_rec :: (a -> Bool) -> [a] -> ([a], [a]) partition_rec _ [] = ([], []) partition_rec p (x : xs) = if p x then (x : ts, fs) else (ts, x : fs) where (ts, fs) = partition_rec p xs -- mit filter partition_filter :: (a -> Bool) -> [a] -> ([a], [a]) partition_filter p xs = (filter p xs, filter (\x -> not (p x)) xs) prop_partition_rec xs = partition_rec even xs == partition even xs prop_partition_filter xs = partition_filter even xs == partition even xs prop_partitionDistrib xs ys = partition even (xs ++ ys) == (xs1 ++ ys1, xs2 ++ ys2) where (xs1, xs2) = partition even xs (ys1, ys2) = partition even ys {- Die ersten Implementierung ist effizienter als die zweite, weil "p" nur einmal pro Element angewandt wird statt zweimal. Die zweite Version ist wahrscheinlich die einfachste. Statt "(\x -> not (p x))" kann man auch "not . p" schreiben (vgl. 6.7 in den Folien). -} {- G4 -} {- Die Evaluierung von "zeros" terminiert nicht: zeros = 0 : zeros = 0 : 0 : zeros = 0 : 0 : 0 : zeros = ... Das sieht man deutlich, wenn man versucht, die Funktion in "ghci" auszuwerten. -} {- H1 -} type DistanceTable = [(String, Integer, String)] citiesOfTable :: DistanceTable -> [String] citiesOfTable table = [x | (x, _, _) <- table] ++ [y | (_, _, y) <- table] doubledTable :: DistanceTable -> DistanceTable doubledTable table = table ++ [(y, k, x) | (x, k, y) <- table] isDistanceTableNonnegative :: DistanceTable -> Bool isDistanceTableNonnegative table = null [() | (x, k, y) <- table, k < 0] isDistanceTableNonreflexive :: DistanceTable -> Bool isDistanceTableNonreflexive table = null [() | (x, k, y) <- table, x == y] isDistanceTableConsistent :: DistanceTable -> Bool isDistanceTableConsistent table = null [() | (x, k, y) <- dtable, (x', k', y') <- dtable, x == x', y == y', k < k'] where dtable = doubledTable table isDistanceTableComplete :: DistanceTable -> Bool isDistanceTableComplete table = all (\p -> p `elem` dtable) cpairs where cities = citiesOfTable table cpairs = [ (x,y) | x <- cities, y <- cities, x /= y ] dtable = map (\(a, _, b) -> (a, b)) $ doubledTable table isDistanceTableTriangleInequality :: DistanceTable -> Bool isDistanceTableTriangleInequality table = null [() | (x, k, y) <- dtable, (y', k', z) <- dtable, y == y', (x', k'', z') <- dtable, x == x', z == z', k + k' < k''] where dtable = doubledTable table isDistanceTableSane :: DistanceTable -> Bool isDistanceTableSane table = isDistanceTableNonnegative table && isDistanceTableNonreflexive table && isDistanceTableConsistent table && isDistanceTableComplete table && isDistanceTableTriangleInequality table {- H2 -} fixpoint :: (a -> a -> Bool) -> (a -> a) -> a -> a fixpoint eq f x = if eq x (f x) then x else fixpoint eq f (f x) {- H3 -} comp :: Eq b => [(a, b)] -> [(b, c)] -> [(a, c)] comp r1 r2 = [(a, c) | (a, b) <- r1, (b', c) <- r2, b == b'] trancl :: Ord a => [(a, a)] -> [(a, a)] trancl r = if r' == step then step else trancl step where r' = sort $ nub r step = sort $ nub $ r' ++ comp r' r' trancl' :: Ord a => [(a, a)] -> [(a, a)] --trancl' r = fixpoint (\r1 r2 -> sort (nub r1) == sort (nub r2)) (\r' -> r' ++ comp r r') r trancl' r = fixpoint (==) (\r' -> sort (nub (r' ++ comp r r'))) (sort (nub r)) {- H4 -} mapIndex :: (Integer -> a -> b) -> [a] -> [b] mapIndex f xs = aux f 0 xs where aux f _ [] = [] aux f n (x:xs) = f n x : aux f (n+1) xs -- kann auch implementiert werden mit: mapIndex' :: (Integer -> a -> b) -> [a] -> [b] mapIndex' f = zipWith f [0..]