FP / Monads (again)

Monads (again)

Functional programming

Let's talk about monads!

But now differently

Function application

($) :: (a -> b) -> a -> b
($) f x = f x

> square $ 5  -- 25
> (^2) $ 5    -- 25
> (+1) $ 5    -- 6

But some values are special

Lists

inc :: [Int] -> [Int]
inc []     = []
inc (n:ns) = n+1 : inc ns

sqr :: [Int] -> [Int]
sqr []     = []
sqr (n:ns) = n^2 : sqr ns

Why is it so complicated?

map

map :: (a -> b) -> [a] -> [b]
map f [] = []
map f (x:xs) = f x : map f xs
inc = map (+1)
sqr = map (^2)

Abstraction!

Why only lists?

More abstraction!

Functor

class Functor f where
    fmap :: (a -> b) -> f a -> f b

For example

instance Functor [] where
    -- fmap :: (a -> b) -> [a] -> [b]
    fmap = map
instance Functor Maybe where
    -- fmap :: (a -> b) -> Maybe a -> Maybe b
    fmap _ Nothing = Nothing
    fmap g (Just x) = Just (g x)
fmap (+1) [3, 5, 8]     -- [4, 6, 9]
fmap (^2) []            -- []
fmap (+1) Nothing       -- Nothing
fmap (^2) (Just 3)      -- Just 9
fmap not (Just False)   -- Just True

Functor laws

Abstract even more!

Multiple arguments?

fmap0 :: a -> f a
fmap1 :: (a -> b) -> f a -> f b
fmap2 :: (a -> b -> c) -> f a -> f b -> f c
fmap3 :: (a -> b -> c -> d) -> f a -> f b -> f c -> f d
...
> fmap2 (+) (Just 1) (Just 2)

Abstract function application!

 ($)  ::   (a -> b) ->   a ->   b
(<*>) :: f (a -> b) -> f a -> f b

Applicative

class Functor f => Applicative f where
    pure :: a -> f a
    (<*>) :: f (a -> b) -> f a -> f b
instance Applicative Maybe where
    -- pure :: a -> Maybe a
    pure = Just
    -- (<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b
    Nothing  <*> _  = Nothing
    (Just g) <*> mx = fmap g mx
> pure (+1) <*> Just 1             -- Just 2
> pure (+) <*> Just 1 <*> Just 2   -- Just 3
> pure (+) <*> Nothing <*> Just 2  -- Nothing
instance Applicative [] where
    -- pure :: a -> [a]
    pure x = [x]
    -- (<*>) :: [a -> b] -> [a] -> [b]
    gs <*> xs = [g x | g <- gs, x <- xs]
> pure (+1) <*> [1,2,3]        -- [2,3,4]
> pure (+) <*> [1] <*> [2]     -- [3]
> pure (*) <*> [1,2] <*> [3,4] -- [3,4,6,8]

Example

5 `div` 0   -- *** Exception: divide by zero
safediv :: Int -> Int -> Maybe Int
safediv x y | y == 0 = Nothing
            | otherwise = Just (x `div` y)
> 5 `safediv` 0
Nothing

How to work with results?

> (5 `safediv` 2) + (9 `safediv` 3)  -- error

Another example

quad :: Double -> Double -> Double -> [Double]
quad a b c | discr <  0 = []
           | discr == 0 = [-(b/(2*a))]
           | discr >  0 = [-((b + sqrt discr) / (2*a)),
                           -((b - sqrt discr) / (2*a))]
    where discr = b^2 - 4*a*c

Apply operation on all results

> (*10) <$> quad 1 2 1
[-10.0]
> (*10) <$> quad 5 25 30
[-30.0,-20.0]
> (*10) <$> quad 1 1 1
[]

Applicative laws

             pure id <*> v == v
pure (.) <*> u <*> v <*> w == u <*> (v <*> w)
         pure f <*> pure x == pure (f x)
              u <*> pure y == pure ($ y) <*> u

Example

sequenceA :: Applicative f => [f a] -> f [a]
sequenceA []     = pure []
sequenceA (x:xs) = pure (:) <*> x <*> sequenceA xs
> sequenceA [Just 1, Just 2, Just 3] -- Just [1, 2, 3]

IO is also Applicative

getChars :: Int -> IO String
getChars n = sequenceA (replicate n getChar)

Generic functions!

Example

data Expr = Val Int | Div Expr Expr

eval :: Expr -> Int
eval (Val n)   = n
eval (Div x y) = eval x `div` eval y
> eval (Div (Val 1) (Val 0)) -- *** Exception: divide by zero
eval :: Expr -> Maybe Int
eval (Val n) = Just n
eval (Div x y) = case eval x of
                   Nothing -> Nothing
                   Just n -> case eval y of
                               Nothing -> Nothing
                               Just m -> safediv n m

Let's try to simplify

eval :: Expr -> Maybe Int
eval (Val n)   = pure n
eval (Div x y) = pure safediv <*> eval x <*> eval y
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
mx >>= f = case mx of
                Nothing -> Nothing
                Just x -> f x
eval :: Expr -> Maybe Int
eval (Val n) = Just n
eval (Div x y) = eval x >>= \n ->
    eval y >>= \m ->
    safediv n m

Monad

class Applicative m => Monad m where
    return :: a -> m a
    (>>=) :: m a -> (a -> m b) -> m b

    return = pure

Example

Relabelling trees

data Tree a = Leaf a | Node (Tree a) (Tree a)
    deriving Show
tree :: Tree Char
tree = Node (Node (Leaf 'a') (Leaf 'b')) (Leaf 'c')
> fst (rlabel tree 0)
Node (Node (Leaf 0) (Leaf 1)) (Leaf 2)

Relabel

rlabel :: Tree a -> Int -> (Tree Int, Int)
rlabel (Leaf _) n = (Leaf n, n+1)
rlabel (Node l r) n = (Node l' r', n'')
    where
        (l',n') = rlabel l n
        (r',n'') = rlabel r n'

Passing state

The state

type State = Int

State Transformer

type ST = State -> State

State Transformer (with result)

type ST a = State -> (a, State)

State Transformer (with constructor)

newtype ST a = S (State -> (a,State))
runState :: ST a -> State -> (a,State)
runState (S st) x = st x

Functor

instance Functor ST where
    -- fmap :: (a -> b) -> ST a -> ST b
    fmap g st = S (\s -> let (x,s') = runState st s 
                         in (g x, s'))

Applicative

instance Applicative ST where
    -- pure :: a -> ST a
    pure x = S (\s -> (x,s))
    -- (<*>) :: ST (a -> b) -> ST a -> ST b
    stf <*> stx = S (\s ->
        let (f,s') = runState stf s
            (x,s'') = runState stx s' in (f x, s''))
fresh :: ST Int
fresh = S (\n -> (n, n+1))

alabel :: Tree a -> ST (Tree Int)
alabel (Leaf _) = Leaf <$> fresh
alabel (Node l r) = Node <$> alabel l <*> alabel r

Monad

instance Monad ST where
  -- (>>=) :: ST a -> (a -> ST b) -> ST b
  st >>= f = S (\s -> let (x,s') = runState st s
                      in runState (f x) s')
mlabel :: Tree a -> ST (Tree Int)
mlabel (Leaf _) = do
    n <- fresh
    return (Leaf n)
mlabel (Node l r) = do
    l' <- mlabel l
    r' <- mlabel r
    return (Node l' r')

Monad laws

         return a >>= k == k a
           m >>= return == m
m >>= (\x -> k x >>= h) == (m >>= k) >>= h

More generic functions

mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM f [] = return []
mapM f (x:xs) = do
    y <- f x
    ys <- mapM f xs
    return (y:ys)
conv :: Char -> Maybe Int
conv c | isDigit c = Just (digitToInt c)
       | otherwise = Nothing
> mapM conv "1234"
Just [1,2,3,4]
> mapM conv "123a"
Nothing
readSingleFile :: FilePath -> IO [String]

readNamesFromFiles :: [FilePath] -> IO [String]
readNamesFromFiles files =
    (fmap concat) $ mapM readSingleFile files