On this page:
17.1 Overview
8.7

17 Modelling effects with Monads

17.1 Overview

There are a few exercises in the file.

../code/Monad3.hs

--------------------------------------------------------------------------------
----- Introduction
--------------------------------------------------------------------------------


todo = undefined

-- Our goal here is to use _pure_ computations to _model_ various side-effects.
-- There are many reasons we might want to do this, but the core reason is that
-- pure values are easier to reason about (for the most part). If you give a
-- pure function the same input, you'll always get the same output.

-- The first question question is "what effects do we want to model?"


--------------------------------------------------------------------------------
----- Reading, Writing, and Both

------- Reading
--
-- It may seem odd initially, but _reading_ values is considered a side-effect.
-- The reason for this is because we might want to have access to a particular
-- value without passing it around explicitly. So being able to _implicitly_
-- access a variable is a side-effect.

-- A 'reader' is just something that always has access to a particular value.
-- Functions do that!
data Reader r a = R (r -> a)

-- The Functor instance for Reader is about changing the value we get back from
-- our Reader by applying the 'mapped' function.
instance Functor (Reader r) where
   fmap f (R g) = R (\x -> f (g x))

-- Running a Reader computation is about providing the value that all of the
-- nest-Reader computations have access to.
runReader :: Reader r a -> r -> a
runReader (R g) r = g r

-- Because the point is to always have access to a value, we need a function
-- that gives us the value for any `Reader`:
request :: Reader r r -- Notice the type!
request = R id

-- Make sure you understand the `Reader` instance of Monad. Notice that the
-- same value is provided to _both_ calls of `runReader`. This is not an
-- accident!
instance Monad (Reader r) where
   return a    = R (const a)
   r >>= k = R (\x -> runReader (k (runReader r x)) x)

---- Example 1:

-- Let's look at using Reader: A configuration is a list of users (the string)
-- and whether they're allowed to do something (the Bool)
data Config = C [(String,Bool)] 

-- We can now write functions that _always have access to this configuation:

checkPermission :: String -> Config -> Bool
checkPermission u (C us) =
  case lookup u us of
    Just b  -> b
    Nothing -> False

processUser :: String -> Reader Config Bool
processUser s = request >>= return . checkPermission s

-- Notice that in the function below we never _see_ the Config. It's only in the type!
-- Despite never mentioning or using the config explicitely, the code is still able
-- to _use_ the config
generateUserReport :: String -> Reader Config String
generateUserReport s = do
  b <- processUser s
  if b
  then return "User was able to access the lab"
  else return (s ++ " attempted to access the lab, despite not having the permissions required")


  
------- Writing
--
-- Writing is also a side-effect, which might be more obvious, but what's
-- important to realize is that writing is not the same as _mutating_. You can
-- think of writing as being similar to logging a process: you can keep adding
-- information, but you can't change the information once you've added it.



-- A `Writer` is something that keeps track of everything we've written so far
data Writer s a = W (s, a)

-- For `Writer` we need a concept of `Monoid`: which you can think of as
-- follows (the actual definition in Haskell is a bit different, but what's
-- shown below is what matters to us)
--
-- Monoid represent things where:
--
-- * we have a special value that can represent the 'empty' value of that type
-- * we can always combine (with `mappend`) and two values of that type to get
-- a new value

-- class Monoid m where
--   mempty  :: m
--   mappend :: m -> m -> m
--   (<>) = mappend

-- Of course, there are laws... we live in a society.
-- mempty <> m      === m
-- m      <> mempty === m

-- To 'write' something we can use the function `tell` which put the written
-- message/value into the tuple we're using to keep track.
tell :: Monoid s => s -> Writer s ()
tell s = W (s, ())

-- To `Run` a writer, we just have to get the tuple out.
runWriter :: Monoid s =>  Writer s a -> (s,a)
runWriter (W v) = v


-- Study the definitions below, make sure you understand the use of `mempty`
-- and `mappend`!
instance Functor (Writer s) where
   fmap f (W (s, a)) = W (s, f a)

instance Monoid s => Monad (Writer s) where
  return x         = W (mempty, x)
  (W (s, x)) >>= k =
    case k x of
      W (s', y) -> W (s `mappend` s', y)

---- Example 2:

-- Let's use `Writer`.

-- Here's a type for a small arithmetic language
data Arith = ANum Int
           | AAdd Arith Arith
           | AMul Arith Arith
           | ANeg Arith
           | ASub Arith Arith
  deriving (Show, Eq)

-- Here's a data type for a small stack-based machine for calculating arithmetic
-- expressions
data Instruction = Push Int
                 | Add
                 | Sub
                 | Mul
                 | Neg
                 | Div
 deriving (Show, Eq)

-- Let's compile `Arith` into `Instruction`
compile1 :: Arith -> [Instruction]
compile1 (ANum i)   = [Push i]
compile1 (AAdd a b) = compile1 a ++ compile1 b ++ [Add]
compile1 (AMul a b) = compile1 a ++ compile1 b ++ [Mul]
compile1 (ANeg a)   = compile1 a ++ [Neg]
compile1 (ASub a b) = compile1 a ++ compile1 b ++ [Sub]


-- That's all well and good, but what if we wanted a trace of how the
-- compilation occured? It would be hard to change the code about to produce
-- such a trace.
--
-- Instead we can write `compile` as a `Writer` computation, so that we're
-- always able to log what we're doing:

compile2 :: Arith -> Writer String [Instruction]
compile2 (ANum i)   = do
  tell "Compiling an integer\n"
  return [Push i]
compile2 (AAdd a b) = do
  tell "Compiling an Add\n"
  a' <- compile2 a
  b' <- compile2 b
  return (a' ++ b' ++ [Add])
compile2 (AMul a b) = do
  tell "Compiling Mul\n"
  a' <- compile2 a
  b' <- compile2 b
  return (a' ++ b' ++ [Mul])
compile2 (ANeg a)   = do
  tell "compiling Neg\n"
  a' <- compile2 a
  return (a' ++ [Neg])
compile2 (ASub a b) = do
  tell "compiling sub\n"
  a' <- compile2 a
  b' <- compile2 b
  return (a' ++ b' ++ [Sub])

-- Bonus exercise: The code above does a lot of the same over and over. Figure
-- out a way to rewrite `compile2` so that all binary operators use the same
-- helper function
--
-- The function above is treating the writer as a way to log information while
-- computing a value. Let's try a different thing, see if you can figure out
-- what this is doing:

compile3 :: Arith -> Writer [Instruction] Int
compile3 (ANum i)   = do
  tell [Push i]
  return i
compile3 (AAdd a b) = do
  a' <- compile3 a
  b' <- compile3 b
  tell [Add]
  return (a' + b')
compile3 (AMul a b) = do
  a' <- compile3 a
  b' <- compile3 b
  tell [Mul]
  return (a' * b')
compile3 (ANeg a)   = do
  a' <- compile3 a
  tell [Neg]
  return (-a')
compile3 (ASub a b) = do
  a' <- compile3 a
  b' <- compile3 b
  tell [Sub]
  return (a' - b')


------- Reading and Writing
--
-- Combining the two concepts above gives us a notion of a computation that can
-- `Read` and `Write`. However, the reading and writing are _separate_ effects,
-- so the thing we're writing and the thing we're reading aren't the same thing:


-- A `Reader/Writer` is basically the combination of the two types from before.
data RW r w a = RW (r -> (w, a))

instance Functor (RW r w) where
  fmap f (RW g) = RW ((fmap . fmap) f g) -- Make sure you understand this line
                                         -- It may help to step through the
                                         -- `fmap`s

instance Monoid w => Monad (RW r w) where
  return x = RW (\r -> (mempty, x))
  -- bind :: RW r w a -> (a -> RW r w b) -> RW r w b
  (RW f) >>= k = todo




















instance Applicative (RW r w) where
  pure = undefined
  (<*>) = undefined


instance Applicative (Writer s) where
  pure = undefined
  (<*>) = undefined


instance Applicative (Reader r) where
  pure = undefined
  (<*>) = undefined