Funktionale Programmierung Complete

download Funktionale Programmierung Complete

of 50

Transcript of Funktionale Programmierung Complete

  • 7/28/2019 Funktionale Programmierung Complete

    1/50

    Funktionale Programmierung mitHaskell

    Jannis Harder

    MetaNook25. November 2011

  • 7/28/2019 Funktionale Programmierung Complete

    2/50

    Warum?

  • 7/28/2019 Funktionale Programmierung Complete

    3/50

    FunktionaleProgrammierung

  • 7/28/2019 Funktionale Programmierung Complete

    4/50

    Funktionen sind

    FunktionenUnd keine Prozeduren, Methoden, Befehle oderAnweisungen

  • 7/28/2019 Funktionale Programmierung Complete

    5/50

    Funktionen sind WerteGenauso wie Zahlen, Listen, Texte, Bume, Bilder

  • 7/28/2019 Funktionale Programmierung Complete

    6/50

    Auer Wertenund damit auch Funktionen

    gibt es nichts

  • 7/28/2019 Funktionale Programmierung Complete

    7/50

    Haskell

  • 7/28/2019 Funktionale Programmierung Complete

    8/50

    Erste Eindrcke

    quicksort [] = []quicksort (p:xs) = quicksort low ++ [p]

    ++ quicksort highwhere (low, high) = partition (< p) xs

    primes = nubBy (\n p > n `mod` p == 0) [2..]

  • 7/28/2019 Funktionale Programmierung Complete

    9/50

    Anwenden von Funktionen

    ghci> sqrt 255.0ghci> min 42 55ghci> 3 * 7 + 223ghci> (+) ((*) 3 7) 223ghci> 345 `mod` 105ghci> min 5 4 + 26ghci> min 5 (4 + 2)5

  • 7/28/2019 Funktionale Programmierung Complete

    10/50

    Booleans und Strings

    Prelude> not TrueFalsePrelude> True && FalseFalsePrelude> True || FalseTruePrelude> length "Foobar"6Prelude> reverse "!dlrow,olleH"

    "Hello,

    world!"

  • 7/28/2019 Funktionale Programmierung Complete

    11/50

    Typen

    Prelude> not "True"Couldn't match expected type `Bool' with actual type `[Char]'In the first argument of `not', namely `"True"'In the expression: not "True"

    Prelude> :type TrueTrue :: BoolPrelude> :t "True""True" :: [Char]Prelude> :t not

    not :: Bool > BoolPrelude> :t not Truenot True :: Bool

  • 7/28/2019 Funktionale Programmierung Complete

    12/50

    Eigene Definitionen

    definitions.hs

    doubleMe x = x + x

    Prelude> :load definitions.hs[1 of 1] Compiling MainOk, modules loaded: Main.*Main> doubleMe 5

    10

  • 7/28/2019 Funktionale Programmierung Complete

    13/50

    Alles neu definieren

    tripleMe x = 3 * x

    *Main> :reloadOk, modules loaded: Main.*Main> tripleMe 515*Main> doubleMe 5Not in scope: `doubleMe'

    M

  • 7/28/2019 Funktionale Programmierung Complete

    14/50

    Mehr Argumente und Currying

    implies a b = not a || b

    *Main> :r*Main> True `implies` False

    False*Main> implies False FalseTrue*Main> (implies False) FalseTrue

    *Main> :t impliesimplies :: Bool > (Bool > Bool)*Main> :t implies Falseimplies False :: Bool > Bool

  • 7/28/2019 Funktionale Programmierung Complete

    15/50

    Listen

    *Main> [1,2,3,4][1,2,3,4]*Main> 1:(2:(3:(4:[])))[1,2,3,4]*Main> 1:2:3:4:[][1,2,3,4]*Main> head [1,2,3,4]1*Main> tail [1,2,3,4][2,3,4]*Main> ['F','o','o']

    "Foo"*Main> [True, 'o']Couldn't match expected type `Bool' with actual type `Char'

    M b ?

  • 7/28/2019 Funktionale Programmierung Complete

    16/50

    Maybe?

    *Main> [Just 1, Nothing][Just 1,Nothing]*Main> find (> 9000) [1,2,3]

    Nothing*Main> find (== 2) [1,2,3]Just 2*Main> :t Just "something"Just "something" :: Maybe [Char]

    l

  • 7/28/2019 Funktionale Programmierung Complete

    17/50

    Tupel

    *Main> (True, 'o')(True,'o')*Main> :t (True, 'o')(True, 'o') :: (Bool, Char)*Main> fst (True, 'o')True*Main> snd (True, 'o')'o'

    *Main> (False, '5', 23)(False, '5', 23)

    P l

  • 7/28/2019 Funktionale Programmierung Complete

    18/50

    Polymorphie

    *Main> :t "Foo""Foo" :: [Char]*Main> :t [True, True, False][True, True, False] :: [Bool]*Main> :t [][] :: [a]

    *Main> :t headhead :: [a] > a*Main> :t (:)(:) :: a > [a] > [a]

    *Main> :t (,)(,) :: a > b > (a, b)*Main> :t fstfst :: (a, b) > a

    B h kt P l h

  • 7/28/2019 Funktionale Programmierung Complete

    19/50

    Beschrnkte Polymorphie

    *Main> 42 == 42True*Main> "Foo" == "Bar"

    False*Main> '0' == "0" expected type `Char' actual type `[Char]'*Main> reverse == tailNo instance for (Eq ([a0] > [a0]))

    T kl

  • 7/28/2019 Funktionale Programmierung Complete

    20/50

    Typklassen

    *Main> :t (==)(==) :: Eq a => a > a > Bool*Main> :info Eqclass Eq a where

    (==) :: a > a > Bool(/=) :: a > a > Bool

    instance Eq Integerinstance Eq Charinstance Eq a => Eq [a]...

    M h Li t

  • 7/28/2019 Funktionale Programmierung Complete

    21/50

    Mehr Listen

    *Main> [1..5][1,2,3,4,5]*Main> ['a'..'z']"abcdefghijklmnopqrstuvwxyz"*Main> [ x^2 | x [ x | x [(x, y) | x

  • 7/28/2019 Funktionale Programmierung Complete

    22/50

    Pattern Matching

    isEmptyList [] = TrueisEmptyList _ = False

    orElse (Just a) _ = aorElse Nothing b = b

    majority False False _ = Falsemajority True True _ = Truemajority _ _ x = x

    end l = case reverse l ofh : _ > h

    P tt M t hi II

  • 7/28/2019 Funktionale Programmierung Complete

    23/50

    Pattern Matching II

    *Main> isEmpty ""True*Main> (find (>5) [1,2,3]) `orElse` 0

    0*Main> (find (>5) [9,8,7]) `orElse` 09*Main> end "Haskell!"'!'

    If nd G d

  • 7/28/2019 Funktionale Programmierung Complete

    24/50

    If und Guards

    sizeOfNumber x =if x > 9000 then "gigantisch" else "winzig"

    sizeOfNumber' x | x > 9000 = "gigantisch"| x < 100 = "winzig"

    | otherwise = "normal"

    *Main> [sizeOfNumber x | x [sizeOfNumber' x | x

  • 7/28/2019 Funktionale Programmierung Complete

    25/50

    Rekursion

    selectNth 0 (h : _) = hselectNth n (_ : t) = selectNth (n 1) t

    fibonacci = 0 : 1 : [ a + b |(a, b)

  • 7/28/2019 Funktionale Programmierung Complete

    26/50

    Funktionen hherer Ordnung

    *Main> succ 12*Main> map succ [0,2,2,6][1,3,3,7]*Main> :t map

    map :: (a > b) > [a] > [b]*Main> map (reverse . map succ) ["Foo", "Bar"]["ppG","sbC"]*Main> :t (.)(.) :: (b > c) > (a > b) > a > c*Main> foldr (++) "!" ["Foo", "Bar", "Baz"]"FooBarBaz!"

    F nkti nen hherer Ordn ng II

  • 7/28/2019 Funktionale Programmierung Complete

    27/50

    Funktionen hherer Ordnung II

    collatzStep x | x `mod` 2 == 0 = x `div` 2

    | otherwise = 3 * x + 1collatzSequence =takeWhile (> 1) . iterate collatzStep

    collatzNumber = length . collatzSequence

    *Main> :t iterateiterate :: (a > a) > a > [a]*Main> :t takeWhiletakeWhile :: (a > Bool) > [a] > [a]*Main> collatzSequence 11[11,34,17,52,26,13,40,20,10,5,16,8,4,2]*Main> collatzNumber 27111

    A sdrcke nd lokale Definitionen

  • 7/28/2019 Funktionale Programmierung Complete

    28/50

    -Ausdrcke und lokale Definitionen

    *Main> map (\x > x ^ 3 x ^ 2) [1,2,3,4][0,4,18,48]*Main> let f x = x ^ 3 x ^ 2 in map f [1,2,3,4][0,4,18,48]

    Eigene Datentypen

  • 7/28/2019 Funktionale Programmierung Complete

    29/50

    Eigene Datentypen

    data Color = Red | Green | Blue | Orangederiving (Show, Read, Eq)

    data Size = XS | S | M | L | XL | XXL | XXXLderiving (Show, Read, Eq, Ord)

    data Shape = Circle Float| Rectangle Float Float| Polygon [(Float, Float)]deriving (Show, Eq)

    data Person = Person { name :: String

    , age :: Int} deriving (Show, Eq)

    Eigene Datentypen II

  • 7/28/2019 Funktionale Programmierung Complete

    30/50

    Eigene Datentypen II

    *Main> [Red, Green, Blue][Red,Green,Blue]*Main> Red == Green

    False*Main> [Circle 2.3, Rectangle 5 6][Circle 2.3, Rectangle 5 6]*Main> name (Person "Jannis" 20)"Jannis"

    Eigene polymorphe Datentypen

  • 7/28/2019 Funktionale Programmierung Complete

    31/50

    Eigene polymorphe Datentypen

    data OneOrTwo a = One a| Two a aderiving (Show, Eq, Ord)

    data List a = Empty | Cons a (List a)deriving (Show, Eq, Ord)

    data Tree a = Nil | Branch a (Tree a) (Tree a)

    deriving (Show, Eq, Ord)

    Eigene polymorphe Datentypen

  • 7/28/2019 Funktionale Programmierung Complete

    32/50

    Eigene polymorphe Datentypen

    *Main> [One 1, Two 2 3][One 1,Two 2 3]*Main> Two "Meta" "Meute"Two "Meta" "Meute"

    Eigene Typklassen

  • 7/28/2019 Funktionale Programmierung Complete

    33/50

    Eigene Typklassen

    class Empty a whereempty :: aisEmpty :: a > Bool

    instance Empty [a] where

    empty = []isEmpty [] = TrueisEmpty _ = False

    instance Empty (Tree a) where

    empty = NilisEmpty Nil = TrueisEmpty _ = False

    Eigene Typklassen

  • 7/28/2019 Funktionale Programmierung Complete

    34/50

    Eigene Typklassen

    *Main> isEmpty ""True*Main> isEmpty [1,2,3]

    False*Main> isEmpty (Branch 1 Nil Nil)False*Main> empty :: Tree IntNil

    Functors

  • 7/28/2019 Funktionale Programmierung Complete

    35/50

    Functors

    *Main> :info Functorclass Functor f where

    fmap :: (a > b) > f a > f binstance Functor Maybeinstance Functor []*Main> fmap (+1) [1, 2][2,3]*Main> fmap (+1) (Just 1)Just 2

    *Main> fmap (+1) NothingNothing

    Eigene Funktor-Instanzen

  • 7/28/2019 Funktionale Programmierung Complete

    36/50

    Eigene Funktor Instanzen

    instance Functor OneOrTwo wherefmap f (One a) = One (f a)fmap f (Two a b) = Two (f a) (f b)

    instance Functor Tree wherefmap _ Nil = Nilfmap f (Branch a l r) =

    Branch (f a) (fmap f l) (fmap f r)

    Eigene Funktor-Instanzen

  • 7/28/2019 Funktionale Programmierung Complete

    37/50

    Eigene Funktor Instanzen

    *Main> fmap (*2) (One 1)One 2*Main> fmap (*2) (Two 2 3)One 4 6

    *Main> fmap (reverse)(Branch "Meta"

    (Branch "Meute" Nil Nil)Nil)

    Branch "ateM" (Branch "etueM" Nil Nil) Nil

    Monads

  • 7/28/2019 Funktionale Programmierung Complete

    38/50

    Monads

    *Main> :info Monadclass Monad m where(>>=) :: m a > (a > m b) > m breturn :: a > m a

    instance Monad Maybe

    instance Monad []instance Monad IO

    join :: Monad m => m (m a) > m a

    liftM :: Monad m => (a > b) > m a > m bm >>= f = join (liftM f m)

    Monads II

  • 7/28/2019 Funktionale Programmierung Complete

    39/50

    Mo a IIfoo l = l >>= \x > [2 * x, 4 * x]bar m = m >>= \x > if x > 10

    then return x 10else Nothing

    *Main> foo [1,2,3][2,4,4,8,6,12]*Main> foo (return 5)[10,20]*Main> bar NothingNothing*Main> bar (Just 5)Nothing*Main> bar (Just 20)Just 10

    Do-Notation

  • 7/28/2019 Funktionale Programmierung Complete

    40/50

    N

    foo l = dox

  • 7/28/2019 Funktionale Programmierung Complete

    41/50

    A g

    *Main> getLine

    metameute"metameute"*Main> :t getLinegetLine :: IO String*Main> putStrLn "metameute"

    metameute*Main> :t putStrLnputStrLn :: String > IO ()*Main> getLine >>= putStrLnmetameute

    metameute*Main> getLine >>= putStrLn . reversemetanookkoonatem

    Ein- und Ausgabe mit do-Notation

  • 7/28/2019 Funktionale Programmierung Complete

    42/50

    g

    hier die collatz funktionenmain = do

    handleOneInputmain

    handleOneInput = don

  • 7/28/2019 Funktionale Programmierung Complete

    43/50

    import Data.Maybeimport Data.List

    import Data.Functorimport Control.Monad

    Hilfe!

  • 7/28/2019 Funktionale Programmierung Complete

    44/50

    H

    Buch: Learn You a Haskell for Great Goodvon Miran Lipovaahttp://learnyouahaskell.com

    Buch: Real World Haskell

    von Bryan OSullivan, Don Stewart und John Goerzenhttp://book.realworldhaskell.org/ Suchmaschine: Hayoo

    http://holumbus.fh-wedel.de/hayoo/hayoo.html

    Suchmaschine: Hooglehttp://www.haskell.org/hoogle/ IRC: #haskell im FreeNode-Netzwerk.

  • 7/28/2019 Funktionale Programmierung Complete

    45/50

    Weitere funktionale

    Programmiersprachen

    Lisp und Scheme

  • 7/28/2019 Funktionale Programmierung Complete

    46/50

    p

    (let ((list '(print "HelloWorld")))

    (print list)(eval list))

    ML

  • 7/28/2019 Funktionale Programmierung Complete

    47/50

    fun fact (n) = if n=0 then 1 else n*fact(n1);

    Scala

  • 7/28/2019 Funktionale Programmierung Complete

    48/50

    List(1,2,3,4,5) map {l => System.out.println(l) }

  • 7/28/2019 Funktionale Programmierung Complete

    49/50

    Erlang

  • 7/28/2019 Funktionale Programmierung Complete

    50/50

    http://goo.gl/ZYj64