view exercises/src/Exercise_15.hs @ 39:9a7b9e0c9eb0 default tip

week 15 tutorial
author Markus Kaiser <markus.kaiser@in.tum.de>
date Fri, 08 Feb 2013 00:06:20 +0100
parents a10156e1609a
children
line wrap: on
line source

module Exercise_15 where

{-
Wichtiges:
    - Syntax: Typannotation, Assoziativität, Pattern Matching, Guards, Currying, List Comprehensions
    - Typisierung: Typvariablen, Typklassen, Typbestimmung
    - QuickCheck
    - Induktionsbeweise: Schema!, Fallunterscheidung, Generalisierung, Strukturelle Induktion
    - Higher Order Functions: map, filter, fold, Lambdas, (.)
    - Pointfree Notation
    - Module, Typlassen, Instanzen
    - Datentypen: data vs. type vs. newtype, Abstraktionsfunktionen
    - (Huffman, Parser)
    - Lazy Evaluation: Redexes, Outside In, Unendliche Datenstrukturen
    - IO: do-Notation, warum die Sonderbehandlung?
    - Endrekursion und Akkumulatoren
-}


-- $
-- f (g x) == f $ g x
-- f $ g $ h $ i x == f . g . h $ i x == (f . g . h . i) x

doubleAllEven xs = map (*2) (filter even xs)
doubleAllEven' xs = map (*2) $ filter even xs



-- Unendliche Datenstrukturen
nats = [1..]
nats' = 1 : map (+1) nats'

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)



-- (.).(.)
-- f (g x y) == (f ((.).(.)) g) x y
oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d
oo = (.).(.)
oo' w = ((.) . (.)) w
oo'' w = (.) ((.) w)
oo''' w x = (.) ((.) w) x
oo'''' w x = ((.) w) . x
oo''''' w x y = (((.) w) . x) y
oo'''''' w x y = w . (x y)
oo''''''' w x y z = (w . (x y)) z
oo'''''''' w x y z = w (x y z)



-- map, fold
-- [f x y | x <- xs, y <- ys, p y]
-- == concatMap (\x -> map (\y -> f x y) (filter p ys)) xs

map' :: (a -> b) -> [a] -> [b]
map' f xs = [f x | x <- xs]

map'' f = foldr g []
    where
    g x xs = (f x) : xs
    --    == (:) (f x)-}
    --    == ((:) . f)-}

map''' f = foldl (\xs x -> xs ++ [f x]) []

foldl' :: (a -> b -> a) -> a -> [b] -> a
foldl' _ acc [] = acc
foldl' f acc (x : xs) = foldl' f (f acc x) xs

foldr' _ acc [] = acc
foldr' f acc (x : xs) = f x (foldr' f acc xs)

filterMap :: (a -> Maybe b) -> [a] -> [b]
filterMap _ [] = []
filterMap f (x:xs) =
        case (f x) of
                Nothing -> filterMap f xs
                Just y  -> y : filterMap f xs



-- type vs. newtype vs. data
type Name = String
greet :: Name -> String
greet n = "Hallo, " ++ n ++ "!"

newtype Address = Address String
askForTheWay (Address a) = "How do I get to " ++ a ++ "?"

data MyList a = Empty | Element a (MyList a) deriving (Eq)
instance Show a => Show (MyList a) where
        show Empty = "[]"
        show (Element a xs) = show a ++ ":" ++ show xs

myLength :: (MyList a) -> Int
myLength Empty = 0
myLength (Element _ xs) = 1 + myLength xs



-- Baumdefinitionen
data BinaryTree a = Empty | Node a (BinaryTree a) (BinaryTree a)

data ArbitraryTree a = Empty | Node a [ArbitraryTree a]