Functors, monads, applicatives and traversables
Given the definition
newtype Map k v = MkMap [(k, v)]
What is the kind of
Map
? Please makeMap k
an instance ofFunctor
.Show that the definition of the arithmetic evaluator using
next
in Lecture 10 is the same as the one using nestedcase
clauses by expanding the definition of the former.Define a function
tuple :: Monad m => m a -> m b -> m (a, b)
using explicit(>>=)
,do
-notation and applicative operators.What does the function do for the
Maybe
monad?
Define the following set of actions for
State s a
:- A computation
get
of typeState s s
that obtains the current value of the state. - A function
modify
of type(s -> s) -> State s ()
that updates the current state using the given function. - A function
put
of types -> State s ()
that overwrites the current state with the given value.
Using those primitive operations:
Define
modify
usingget
andput
.Define
put
usingmodify
.
- A computation
Explain the behavior of
sequence
for theMaybe
monad.Define a monadic generalisation of
foldl
:foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a
Show that the
Maybe
monad satisfies the monad laws.Given the type:
data Expr a = Var a | Val Int | Add (Expr a) (Expr a)
of expressions built from variables of type
a
, show that this type is monadic by completing the following declaration:instance Monad Expr where -- return :: a -> Expr a return x = ... -- (>>=) :: Expr a -> (a -> Expr b) -> Expr b Var a) >>= f = ... (Val n) >>= f = ... (Add x y) >>= f = ... (
With the aid of an example, explain what the
(>>=)
operator for this type does.To show how
(>>=) :: Monad m => m a -> (a -> m b) -> m b
generalizes function application and howdo
-notation generalizeslet
-bindings, consider the following definition of function application with the arguments swapped:(&) :: a -> (a -> b) -> b &) = flip ($) (
Then, we can consider
let x = a in b
to be syntactic sugar for
& \x -> b a
similar to how
do <- a x b
is syntactic sugar for
>>= \x -> b a
Please desugar the following definition into code that explicitly uses
(&)
:= compute x let a = x + 5 = a * 3 b = b / 2 c = c - 7 d = d * d e in e
Please desugar the following definition into code that explicitly uses
(>>=)
:= do main putStrLn "Enter the first number:" <- readLn num1 putStrLn "Enter the second number:" <- readLn num2 putStrLn $ "The sum of the numbers is: " ++ show (num1 + num2)
Given the type:
data Error m a = Error m | OK a
Give a
Functor
instance forError m
. Please explain in words what this functor instance achieves.Give an
Applicative
instance forError m
that we can use to accumulate errors, meaning that we accumulate all error messages of all subcomputations that fail.Give a
Monad
instance forError m
. Please explain what thisMonad
instance can be used for. Please explain how the inducedApplicative
instanceinstance Applicative (Error m) where pure = return <*>) mf ma = do (<- mf f <- ma a return (f a)
differs in behaviour from the error accumulation instance we defined previously.
Given the types
newtype State s a = State {runState :: s -> (a, s)} type StatePassing s a b = (a, s) -> (b, s)
Define functions
statePass :: (a -> State s b) -> StatePassing s a b unStatePass :: StatePassing s a b -> (a -> State s b) statePass' :: State s b -> StatePassing s () b unStatePass' :: StatePassing s () b -> State s b
such that
statePass . unStatePass = id
,unStatePass . statePass = id
,statePass' . unStatePass' = id
andunStatePass' . statePass' = id
.Give a
Monad
instance forState s
where you definereturn
and>>=
in terms of the four functions above.Prove that these definitions of
return
and>>=
are equivalent to the usual definitionsinstance Monad (State s) where return a = State (\s -> (a, s)) State f) >>= g = State (\s -> let (a, s') = f s in let State h = g a in h s') (
Using the four
StatePassing
helper functions we defined above, defineget :: State s s put :: s -> State s () modify :: (s -> s) -> State s ()
We see that code written in the
State s
monad is equivalent to code in “state passing style”, i.e. code where in place of functions of typeA -> B
we instead work with functions of type(A, s) -> (B, s)
that always thread through an extra argument and return value (the state) of types
.(Challenging) Given the types
newtype Cont r a = Cont { runCont :: (a -> r) -> r} type ContPassing r a b = (b -> r) -> (a -> r)
Define functions
contPass :: (a -> Cont r b) -> ContPassing r a b unContPass :: ContPassing r a b -> (a -> Cont r b) contPass' :: Cont r b -> ContPassing r () b unContPass' :: ContPassing r () b -> Cont r b
such that
contPass . unContPass = id
,unContPass . contPass = id
,contPass' . unContPass' = id
andunContPass' . contPass' = id
.Give a
Monad
instance forCont r
. Hint: you may want to use the functions we defined previously.Define a function
callCC :: ((a -> Cont r b) -> Cont r a) -> Cont r a
Hint: you may want to define
callCC
in terms of a helper functioncallCCHelp :: (ContPassing r a b -> ContPassing r () a) -> ContPassing r () a
that you define first.
We see that code written in the
Cont r
monad is equivalent to code in “continuation passing style”, i.e. code where in place of functions of typeA -> B
we instead write functions of type(B -> r) -> (A -> r)
that operate in reverse on “continuations”.Context: similarly to how
State
monads allow us to emulate computation with non-local data flow through mutable variables,Cont
(inuation) monads can be used to emulate computation with non-local control flow where stack discipline is not respected in the call stack and we can instead perform arbitrary reads and writes of the current continuation. The example below demonstrates how this can work in practice.fun :: Int -> String = (`runCont` id) $ do fun n <- callCC $ \exit1 -> do -- define "exit1" str < 10) (exit1 (show n)) when (n let ns = map digitToInt (show (n `div` 2)) <- callCC $ \exit2 -> do -- define "exit2" n' length ns) < 3) (exit2 (length ns)) when ((length ns) < 5) (exit2 n) when ((length ns) < 7) $ do when ((let ns' = map intToDigit (reverse ns) dropWhile (=='0') ns') --escape 2 levels exit1 (return $ sum ns return $ "(ns = " ++ (show ns) ++ ") " ++ (show n') return $ "Answer: " ++ str when :: (Applicative f) => Bool -> f () -> f () = if p then s else pure () when p s