Tutorium 4

Gruppen 5 und 7
Samuel Teuber
propa@teuber.dev
https://teuber.dev/propa

Klausur Vorbereitung

Für den Haskell Teil sehr nützlich: Ein Cheatsheet

Übungsblätter

  • Heute dabei: Alle schriftlichen Abgaben
  • Online: Fibs korrigiert, Rest von Blatt 3 kommt in den nächsten Tagen
  • Fragen/Probleme?

Aufgabe 1: Fibonacci

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

Aufgabe 2: Collatz

  • Unendliche Liste der Folgenmitglieder für Startwert a0
    collatz :: Int -> [Int]
    collatz m = iterate next m
      where
              next :: Int -> Int
              next an
                  | an `mod` 2 == 0 = an `div` 2
                  | otherwise = 3 * an + 1
    
  • Zählen bis zur ersten 1
    num m = length (takeWhile (/= 1) collatz m))
    
  • Suche nach maximalem num in Interval
    maxNum a b = foldl maxPair (0,0) (map (\m -> (m, num m)) [a..b])
      where maxPair (m,n) (m',n') = if n > n' then (m,n) else (m',n')
    

Aufgabe 3: Prime Powers

Klausuraufgabe

  • Merge auf unendlichen Listen
    merge [] b = b
    merge a [] = a
    merge l1@(x:xs) l2@(y:ys)
      | (x<y) = x:merge xs l2
      | otherwise = y:merge l1 ys
    
  • Erste $n$ Potenzen aller Primzahlen
    primepowers n = foldr merge [] [map (^i) primes | i <- [1..n]]
    

Wollen wir statt Klassen einfach Tupel benutzen?

type Name = (String, String)
type MNumber = Integer -- Für die Addition von Matrikelnummern...
type Address = (String, Integer, String) -- Straße, PLZ und Ort
type Grades = [(String, Double)] -- Fach Name und Note
type Student = (Name,MNumber, Address, Grades)

Ist das eine gute Idee?

NEIN

  • Tupel könnte für beliebige Werte benutzt werden
  • Kaum/Keine explizite Bedeutung

Algebraische Datentypen

Definition neuer Typen durch Auflistung aller Konstruktoren:

data Address = Address String Integer String
data UniversityPerson = Student String Integer Address
                        | Professor String Address

Ergibt die folgenden Konstruktoren:

Address :: String -> Integer -> String -> Address
Student :: String -> Integer -> Adress -> UniversityPerson
Professor :: String -> Adress -> UniversityPerson

Jede*r Student und jede*r Professor ist eine UniversityPerson

Pattern-Matching

In [1]:
data UniversityPerson = Student String Integer
                        | Professor String
getName :: UniversityPerson -> String
getName (Student name _) = name
getName (Professor name)  = name

getName (Student "Samuel" 424242)
getName (Professor "Prof. Dr. Snelting")
"Samuel"
"Prof. Dr. Snelting"

Polymorphe Algebraische Datentypen

z.B. Realisierung von optionalen Werten:

data Maybe t = Nothing | Just t
Just True :: Maybe Bool

Polymorphe Rekursive Algebraische Datentypen

data Tree t = Leaf t | Node (Tree t) t (Tree t)

Typklassen

...endlich...

  • Zusammenfassen von Typen anhand von definierter Operationen
  • Java: ~Interfaces Beispiel Eq:
    class Eq t where
      (==) :: t -> t -> Bool
      (/=) :: t -> t -> Bool
    
    Default Implementierungen:
    x /= y = not (x == y)
      x == y = not (x /= y)
    

Typklassen implementieren

instance Eq Bool where
    True == True = True
    False == False = True
    x == y = False

Auch für Polymorphe Typen:

data Maybe t = Nothing | Just t

class Defaultable t where
    getDefault :: (t a) -> a -> a

instance Defaultable Maybe where
    getDefault (Just x) c = x
    getDefault Nothing c = c
In [2]:
data Maybe t = Nothing | Just t
class Defaultable t where
    getDefault :: (t a) -> a -> a
instance Defaultable Maybe where
    getDefault (Just x) c = x
    getDefault Nothing c = c

getDefault (Nothing) 1
getDefault (Just 10) 1
Redundant bracket
Found:
(t a) -> a -> a
Why Not:
t a -> a -> a
Redundant bracket
Found:
(Nothing)
Why Not:
Nothing
1
10

Typklassen Vererbung

510px-Base-classes.svg.png

In [3]:
:t foldr
foldr :: forall (t :: * -> *) a b. Foldable t => (a -> b -> b) -> b -> t a -> b

Automatische Instanziierung

...für algebraische Datenstrukturen
Basierend auf innenliegenden Typen:

In [4]:
data Shape = Circle Double | Rectancle Double Double deriving Eq

Übungsaufgaben

Übungsaufgabe

Befindet sich ein Element in einem Baum?

In [34]:
-- Übungsaufgabe 1
data Tree t = Leaf t | Node (Tree t) t (Tree t)
treeFind :: (Eq a) => Tree a -> a -> Bool
treeFind (Leaf x) y = x == y
treeFind (Node x y z) a = treeFind x a || y==a || treeFind z a
In [35]:
myTree = Node (Node (Leaf "test") "foo" (Leaf "tset")) "abc" (Node (Leaf "42") "bar" (Leaf "24") )
treeFind myTree "test"
treeFind myTree "thisisnotinmytree"
True
False

Übungsaufgabe

Farben vergleichen
TIPP: Pattern Matching!

In [43]:
-- Übungsaufgabe 2
data Colors = Blue | Red | Green

instance Eq Colors where
    Blue == Blue = True
    (==) Red Red = True
    (==) Green Green = True
    (==) x y = False
In [44]:
Blue == Red
Blue == Green
Blue == Blue
False
False
True

Übungsaufgabe

Bäume lesbar machen

In [49]:
data Tree t = Leaf t | Node (Tree t) t (Tree t)
-- Übungsaufgabe 3
instance (Show t) => Show (Tree t) where
    show (Leaf t) = "(Leaf " ++ (show t) ++ ")"
    show (Node x y z) = "(Node " ++ (show x) ++ (show y) ++ (show z)++")"
Redundant bracket
Found:
(show t) ++ ")"
Why Not:
show t ++ ")"
Redundant bracket
Found:
(show x) ++ (show y) ++ (show z) ++ ")"
Why Not:
show x ++ (show y) ++ (show z) ++ ")"
Redundant bracket
Found:
(show y) ++ (show z) ++ ")"
Why Not:
show y ++ (show z) ++ ")"
Redundant bracket
Found:
(show z) ++ ")"
Why Not:
show z ++ ")"
In [50]:
Node (Node (Leaf "test") "foo" (Leaf "tset")) "abc" (Node (Leaf "42") "bar" (Leaf "24") )
(Node (Node (Leaf "test")"foo"(Leaf "tset"))"abc"(Node (Leaf "42")"bar"(Leaf "24")))

Übungsaufabe

map aber für Bäume

In [51]:
-- Übungsaufgabe 4

treeMap :: (a->b) -> Tree a -> Tree b
treeMap op (Leaf x) = Leaf (op x)
treeMap op (Node x y z) = Node (treeMap op x) (op y) (treeMap op z)
In [53]:
myTree = Node (Node (Leaf "test") "foo" (Leaf "tset")) "abc" (Node (Leaf "42") "bar" (Leaf "24") )
treeMap tail myTree
(Node (Node (Leaf "est")"oo"(Leaf "set"))"bc"(Node (Leaf "2")"ar"(Leaf "4")))

Übungsaufgabe

Typklasse für Datenstrukturen die Mappable sind.

Wir wollen eine Typklasse die uns die Funktion dMap :: (a -> b) -> (d a) -> (d b) ermöglicht

In [54]:
-- Übungsaufgabe 5
class Mappable d where
    dMap :: (a -> b) -> (d a) -> (d b)

instance Mappable Tree where
    dMap op t = treeMap op t
Redundant bracket
Found:
(d a) -> (d b)
Why Not:
d a -> (d b)
Redundant bracket
Found:
(d a) -> (d b)
Why Not:
(d a) -> d b
Eta reduce
Found:
dMap op t = treeMap op t
Why Not:
dMap = treeMap

Quickcheck

In [17]:
:!stack install QuickCheck

In [62]:
qsort [] = []
qsort (p:ps) = p:(qsort [x | x <- ps, x <= p]) ++  (qsort [x | x <- ps, x >  p])

qsortCorrect :: [Integer] -> Bool
qsortCorrect list = let list' = (qsort list)
                    in isSorted list' && isPerm list' list
    where
        isSorted:: [Integer] -> Bool
        isSorted [] = True
        isSorted [x] = True
        isSorted (x:y:z) = x<=y && isSorted (y:z)
        isPerm (x:xs) l  = x `elem` l && isPerm xs (delete x l)
        isPerm [] [] = True
        isPerm [] l  = False
        delete x [] = []
        delete x (y:ys)
            | (x==y) = ys
            | otherwise = y : delete x ys

import Test.QuickCheck

quickCheck qsortCorrect
*** Failed! Falsified (after 6 tests and 3 shrinks):
[0,-1]
In [65]:
data Tree t = Leaf | Node (Tree t) t (Tree t)

instance (Show t) => Show (Tree t) where
    show (Leaf) = "()"
    show (Node x y z) = "Node(" ++ (show x) ++ ")" ++ (show y) ++ "(" ++ (show z) ++")"

allTrees :: Int -> t -> [Tree t]
allTrees 0 _ = [Leaf]
allTrees n d = [ (Node x d y) | l <- [0..(n-1)],
                                x <- (allTrees l d),
                                y <- (allTrees (n-l-1) d)]
                                
length (allTrees 5 0)
Redundant bracket
Found:
(Leaf)
Why Not:
Leaf
Redundant bracket
Found:
(show x) ++ ")" ++ (show y) ++ "(" ++ (show z) ++ ")"
Why Not:
show x ++ ")" ++ (show y) ++ "(" ++ (show z) ++ ")"
Redundant bracket
Found:
(show y) ++ "(" ++ (show z) ++ ")"
Why Not:
show y ++ "(" ++ (show z) ++ ")"
Redundant bracket
Found:
(show z) ++ ")"
Why Not:
show z ++ ")"
Redundant bracket
Found:
[(Node x d y) | l <- [0 .. (n - 1)], x <- (allTrees l d), y <- (allTrees (n - l - 1) d)]
Why Not:
[Node x d y | l <- [0 .. (n - 1)], x <- (allTrees l d), y <- (allTrees (n - l - 1) d)]
Redundant bracket
Found:
[(Node x d y) | l <- [0 .. (n - 1)], x <- (allTrees l d), y <- (allTrees (n - l - 1) d)]
Why Not:
[(Node x d y) | l <- [0 .. (n - 1)], x <- allTrees l d, y <- (allTrees (n - l - 1) d)]
Redundant bracket
Found:
[(Node x d y) | l <- [0 .. (n - 1)], x <- (allTrees l d), y <- (allTrees (n - l - 1) d)]
Why Not:
[(Node x d y) | l <- [0 .. (n - 1)], x <- (allTrees l d), y <- allTrees (n - l - 1) d]
42
In [29]:
type Map k v = [(k,v)]
data State r = S (Maybe r) (Map Char (State r))

lookup :: (Eq k) => k -> Map k v -> Maybe v

accepts :: [Char] -> State r -> Maybe r

accepts "" (S e _) = e
accepts (c:cs) (S e m) = let s2 = lookup c m in helper s2
    where
        helper Nothing = Nothing
        helper (Just x) = accepts cs x
Use String
Found:
[Char] -> State r -> Maybe r
Why Not:
String -> State r -> Maybe r
<interactive>:3:1: error:
    The type signature for ‘lookup’ lacks an accompanying binding
      (The type signature must be given where ‘lookup’ is declared)
In [ ]:

In [ ]:

In [ ]: