CSE301

Lab 5 (side-effects and monads)

General instructions

A few imports

We will be using a few pre-defined monads from the standard library in this lab, as well as the list library and system random number generator. Let’s import everything here:

import Control.Monad.State
import Control.Monad.Fail
import System.Random
import Data.List

Note you may have to install some libraries on your machine first to import these modules. On the lab machines, you can install the appropriate libraries by running the following commands from the terminal:

$ cabal update
$ cabal install --lib mtl
$ cabal install --lib random

Basic monadic programming

In class, we considered a few different evaluators for a toy language of arithmetic expressions that included numeric constants, subtraction expressions, and division expressions. Let’s recall here the Haskell data type we used to represent expressions, as well as some example expressions.

data Expr = Con Double | Sub Expr Expr | Div Expr Expr
    deriving (Show,Eq)

e1 = Sub (Div (Con 2) (Con 4)) (Con 3)
e2 = Sub (Con 1) (Div (Con 2) (Con 2))
e3 = Div (Con 1) (Sub (Con 2) (Con 2))

Let’s also recall the monadic version of the first error-handling evaluator, which runs in the Maybe monad in order to handle division-by-zero errors. (This evaluator is called eval1' in the slides, but we have renamed it below.)

evalSafe :: Expr -> Maybe Double
evalSafe (Con c)     = return c
evalSafe (Sub e1 e2) = 
  evalSafe e1 >>= \x1 ->
  evalSafe e2 >>= \x2 ->
  return (x1 - x2)
evalSafe (Div e1 e2) =
  evalSafe e1 >>= \x1 ->
  evalSafe e2 >>= \x2 ->
  if x2 /= 0 then return (x1 / x2) else Nothing

As a warmup exercise, rewrite evalSafe using “do notation” (as seen in class, and also explained here).

-- Exercise 1a
evalSafe :: Expr -> Maybe Double
evalSafe = undefined

The Maybe monad is not the only monad that can be used for error-handling. In fact, the Haskell standard library defines a type class for such monads:

class Monad m => MonadFail (m :: * -> *) where
  fail :: String -> m a

In other words, an instance of MonadFail is a monad m that supports a polymorphic operation “fail” taking a string as argument and returning a value of type m a, for any a.

The Maybe monad provides an instance of MonadFail, where the fail operation simply ignores its string argument:

instance MonadFail Maybe where
  fail s = Nothing

Other instances of MonadFail include the List monad (with fail s = []) and the IO monad (raising an exception). We can witness this behavior for ourselves by running the fail command in the interpreter, with different type annotations added to invoke different instances of the MonadFail class.

Prelude> fail "bad!"
*** Exception: user error (bad!)
Prelude> fail "bad!" :: Maybe Int
Nothing
Prelude> fail "bad!" :: [Int]
[]

Rewrite evalSafe again so that it works with any monad that is an instance of MonadFail, calling the fail operation with a sensible error message in the case of division-by-zero.

-- Exercise 1b
evalSafeMF :: MonadFail m => Expr -> m Double
evalSafeMF = undefined

Then try running it in a few different monads on a few different expressions and see what kind of output it gives you. Record what you see as a comment.

{- different outputs of evalSafeMF ... -}

(Note that by default, the GHC interpreter evaluates expressions in the IO monad, but you can get it to run them in different monads by including a type annotation, as we saw above.)

In class we also saw how to write an error-handling-and-stateful evaluator, which ran in the monad StateT Int Maybe in order to both handle division-by-zero errors and to implement the (admittedly slightly weird) revised semantics of expressions where every third constant (when reading the expression from left-to-right) is interpreted as 0. (This evaluator was called eval3' in the slides, but again we have renamed it below.)

evalWeird :: Expr -> StateT Int Maybe Double
evalWeird (Con c)    =
  get >>= \n ->
  put (n+1) >>= \_ ->
  return (if n `mod` 3 == 2 then 0 else c)
evalWeird (Sub e1 e2) =
  evalWeird e1 >>= \x1 ->
  evalWeird e2 >>= \x2 ->
  return (x1-x2)
evalWeird (Div e1 e2) =
  evalWeird e1 >>= \x1 ->
  evalWeird e2 >>= \x2 ->
  if x2 /= 0 then return (x1/x2) else lift Nothing
evalWeirdTop e = runStateT (evalWeird e) 0 >>= \(x,s) -> return x

Adapt the weird evaluator to implement a slightly modified (and slightly weirder) semantics of expressions, where every third constant is interpreted as 0 when reading the expression from right-to-left. While you’re at it, generalize it to work with any MonadFail monad wrapped in state. Implement this revised semantics as a pair of functions below:

-- Exercise 1c
evalWeird' :: MonadFail m => Expr -> StateT Int m Double
evalWeird' = undefined
evalWeirdTop' :: MonadFail m => Expr -> m Double
evalWeirdTop' = undefined

For example, you should recover the following interpretations:

> evalWeirdTop' e1
-3.0
> evalWeirdTop' (Sub e1 (Con 0)) :: Maybe Double
Nothing

A monad of trees

Sometimes monads are useful even when they do not necessarily correspond in an obvious way to a notion of computation.

Consider the following data type of binary trees with labelled leaves (similar to the data type of binary trees we saw in Lectures 1 and 2, but with the labels shifted from nodes to leaves).

data Bin a = L a | B (Bin a) (Bin a)
  deriving (Show,Eq)

Let’s begin by establishing that the Bin type constructor is a functor. Indeed, we can define an operation of mapping a function over a binary tree analogous to the map operation on lists, and use it as the fmap operation of the Functor class:

mapBin :: (a -> b) -> Bin a -> Bin b
mapBin f (L x)     = L (f x)
mapBin f (B tL tR) = B (mapBin f tL) (mapBin f tR)

instance Functor Bin where
  fmap = mapBin

Prove that Bin really is a functor in the full sense of the word by proving that mapBin satisfies the functor laws:

for all binary trees t :: Bin a and functions f :: b -> c and g :: a -> b.

-- Exercise 2a
{- Your proof goes here -}

Now we will establish that Bin is a monad. To that end, first we have to describe how to define the monadic return and “bind” operations, which in this case will correspond to operations of the following types:

return :: a -> Bin a
(>>=) :: Bin a -> (a -> Bin b) -> Bin b

Moreover, to show that we really have a monad, we need to show that these operations satisfy the monad laws

return x >>= f  = f x
t >>= return    = t
(t >>= f) >>= g = t >>= (\x -> (f x >>= g))

for all values x :: a, binary trees t :: Bin a, and functions f :: a -> Bin b and g :: b -> Bin c.

Define an appropriate instance of the Monad class for Bin:

-- Exercise 2b
instance Monad Bin where
  return = undefined
  (>>=) = undefined

The meaning of “appropriate instance” is left up to you to figure out, but the polymorphic types of return and bind do not leave very many natural possibilities for writing them. Moreover, your implementation should satisfy the monad laws, even if you do not prove that formally in the optional exercise below!

Note that Monad is a superclass of Applicative, so to define a Monad instance you also need to define an instance of Applicative by implementing the operations pure :: a -> m a and (<*>) :: m (a -> b) -> m a -> m b. However, there is a standard way of deriving an instance of Applicative from an instance of Monad, as shown in the boilerplate code below:

instance Applicative Bin where
  pure = return
  fm <*> xm = fm >>= \f -> xm >>= return . f

Prove that the operations you defined above satisfy the monad laws.

-- Exercise 2c (optional)
{- Your proof goes here -}

Can values of the monadic type Bin a be seen as describing effectful computations in some sense? Think about it, and if you eventually find any inspiration (perhaps after completing the other exercises), write down your thoughts below.

-- Exercise 2d (optional)
{- Your thoughts go here -}

Non-deterministic and probabilistic programming

For the following exercises, we introduce our own type class extending the Monad class:

class Monad m => SelectMonad m where
  select :: [a] -> m a

Our intuition is that a “selection monad” is a monad that supports an operation of non-deterministically or probabilistically selecting among a list of values.

A trivial example of a selection monad is the List monad, where select is simply implemented as the identity function:

instance SelectMonad [] where
  select = id

We can think of the List monad as simulating a non-deterministic selection by trying all possible choices.

A different kind of example is provided by the IO monad, where we call the system random number generator to pick one of the elements (the list must be non-empty or the selection fails):

instance SelectMonad IO where
  select xs
    | not (null xs) = do i <- getStdRandom (randomR (0, length xs-1))
                         return (xs !! i)
    | otherwise     = fail "cannot select from empty list"

Finally, the monad of probability distributions provides another interesting example. Formally, the monad itself is defined similarly to the List monad, but where computations are represented as lists of value-probability pairs, rather than simply lists of values.

newtype Dist a = Dist { dist :: [(a,Rational)] }  deriving (Show)

instance Monad Dist where
  return x = Dist [(x,1)]
  xm >>= f = Dist [(y,p*q) | (x,p) <- dist xm, (y,q) <- dist (f x)]
  
-- We add the following standard boilerplate to derive instances of the
-- Functor and Applicative type classes, from the Monad instance above:
instance Functor Dist where
  fmap f xm = xm >>= return . f

instance Applicative Dist where
  pure = return
  xm <*> ym = xm >>= \x -> ym >>= return . x

Non-deterministic selection in the distributions monad may be implemented by taking the uniform distribution on the list of values (again assuming it is non-empty, and otherwise raising an exception):

instance SelectMonad Dist where
  select xs
    | not (null xs) = let n = length xs in Dist [(x, 1 / fromIntegral n) | x <- xs]
    | otherwise     = error "cannot select from empty list"

To illustrate these different implementations of selection monads, consider the following simple program that picks a number between 0 and 3 and then uses it to index into the string “hello”:

code :: SelectMonad m => m Char
code = do
  i <- select [0..3]
  return ("hello" !! i)

Here is a sample transcript of running code in the IO monad (which recall GHCi uses by default). Multiple runs can yield different results, of course:

*Main> code
'l'
*Main> code
'h'

Now running it using the List monad, which always returns the same result:

*Main> code :: [Char]
"hell"

And finally running it using the monad of finite probability distributions, which again always returns the same result:

*Main> code :: Dist Char
Dist {dist = [('h',1 % 4),('e',1 % 4),('l',1 % 4),('l',1 % 4)]}

In the last sample run, observe that our representation of finite probability distributions allows the same value to occur multiple times in the list of value/probability pairs. The following function will compute the total probability of a value occurring in a given distribution, assuming that the values come from an Eq type:

prob :: Eq a => Dist a -> a -> Rational
prob xm x = sum [p | (y,p) <- dist xm, x == y]

Similarly, the following function will normalize a distribution by first computing the list of values in its support, and then returning the probabilities of all those values:

normalize :: Eq a => Dist a -> Dist a
normalize xm = Dist [(x,prob xm x) | x <- support xm]
  where
    support :: Eq a => Dist a -> [a]
    support xm = nub [x | (x,p) <- dist xm, p > 0]  -- "nub", defined in Data.List, removes duplicates

Examples:

*Main> prob code 'l'
1 % 2
*Main> normalize code
Dist {dist = [('h',1 % 4),('e',1 % 4),('l',1 % 2)]}

(Observe that we didn’t need to put any type annotations above, since the type code :: Dist Char is automatically inferred from the calls to prob and normalize.)

Using the SelectMonad class, write a function that “flips a coin” by selecting a boolean value True or False.

-- Exercise 3a
coin :: SelectMonad m => m Bool
coin = undefined

Then use that to write a function that selects an arbitrary subset of elements of a list.

-- Exercise 3b
subset :: SelectMonad m => [a] -> m [a]
subset = undefined

(The elements of the subset may be listed in any order, and if the input list contains duplicates it is okay for the output list to contain duplicates as well.)

You should see results roughly like the following:

*Main> subset [1..3] 
[3]
*Main> subset [1..3] 
[1,3]
*Main> subset [1..3] :: [[Int]]
[[],[1],[2],[1,2],[3],[1,3],[2,3],[1,2,3]]
*Main> subset [1..3] :: Dist [Int]
Dist {dist = [([],1 % 8),([1],1 % 8),([2],1 % 8),([1,2],1 % 8),([3],1 % 8),([1,3],1 % 8),([2,3],1 % 8),([1,2,3],1 % 8)]}

Write a function which takes a monadic computation of a boolean that we think of as an “experiment” and runs it repeatedly, returning how many times it evaluates to True.

-- Exercise 3c
simulate :: Monad m => Int -> m Bool -> m Int
simulate = undefined

Note that the type of simulate indicates that it should work with an arbitrary monad, not just a selection monad.

Here are some more precise requirements:

Examples:

*Main> simulate 100000 coin
49932
*Main> simulate 10000 (subset ['a'..'z'] >>= \xs -> return (elem 'a' xs && elem 'b' xs))
2492
*Main> normalize $ simulate 3 coin
Dist {dist = [(3,1 % 8),(2,3 % 8),(1,3 % 8),(0,1 % 8)]}>

Rémy’s algorithm is an elegant iterative algorithm for generating random binary trees, where each binary tree of a given size is generated with the same probability. In other words, it is a uniform generator for binary trees with a given number of nodes/leaves.

The algorithm for generating a binary tree with n nodes and n+1 leaves can be described as follows:

Here is a little animation of running Rémy’s algorithm to generate a random binary tree with 50 leaves (followed by running the algorithm in reverse to deconstruct the tree):

remy 50
remy 50

Observe that as we grow new leaves, we also label them in the order of creation.

Implement Rémy’s algorithm as a function

-- Exercise 3d (optional)
genTree :: SelectMonad m => [a] -> m (Bin a)
genTree = undefined

that generates a binary tree with a given list of leaf labels.

More precise requirements:

Examples:

> genTree [1,2] :: [Bin Int]
[B (L 1) (L 2),B (L 2) (L 1)]
> prob (genTree [1..4]) (B (L 3) (B (B (L 1) (L 4)) (L 2)))
1 % 120
> prob (genTree [1..4]) (B (B (L 4) (L 1)) (B (L 2) (L 3)))
1 % 120
> genTree [1..50]
B (B (B (B (L 41) (L 43)) (B (B (L 46) (L 38)) (L 39))) (B (B (B (L 1) (L 29)) (B (L 36) (L 21))) (B (B (L 22) (L 47)) (B (L 9) (B (B (L 34) (L 48)) (B (B (B (B (L 13) (L 14)) (L 16)) (L 37)) (B (L 11) (B (B (L 6) (L 44)) (B (L 8) (B (B (B (L 49) (B (L 45) (B (B (L 4) (B (L 28) (B (B (L 24) (B (B (L 23) (L 12)) (B (B (L 2) (B (L 18) (L 19))) (B (L 33) (L 3))))) (L 7)))) (B (L 26) (B (L 40) (B (B (B (L 15) (L 32)) (L 31)) (L 27))))))) (L 5)) (L 35))))))))))) (B (B (B (L 25) (B (B (B (L 42) (L 50)) (L 20)) (L 10))) (L 30)) (L 17))