Last active
August 29, 2015 14:09
-
-
Save j-keck/abc048aa312d5d7c3f25 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
PROGRAMMING WITH EFFECTS | |
Graham Hutton, January 2014 | |
Shall we be pure or impure? | |
The functional programming community divides into two camps: | |
o "Pure" languages, such as Haskell, are based directly | |
upon the mathematical notion of a function as a | |
mapping from arguments to results. | |
o "Impure" languages, such as ML, are based upon the | |
extension of this notion with a range of possible | |
effects, such as exceptions and assignments. | |
Pure languages are easier to reason about and may benefit | |
from lazy evaluation, while impure languages may be more | |
efficient and can lead to shorter programs. | |
One of the primary developments in the programming language | |
community in recent years (starting in the early 1990s) has | |
been an approach to integrating the pure and impure camps, | |
based upon the notion of a "monad". This note introduces | |
the use of monads for programming with effects in Haskell. | |
Abstracting programming patterns | |
-------------------------------- | |
Monads are an example of the idea of abstracting out a common | |
programming pattern as a definition. Before considering monads, | |
let us review this idea, by means of two simple functions: | |
inc :: [Int] -> [Int] | |
inc [] = [] | |
inc (n:ns) = n+1 : inc ns | |
sqr :: [Int] -> [Int] | |
sqr [] = [] | |
sqr (n:ns) = n^2 : sqr ns | |
Both functions are defined using the same programming pattern, | |
namely mapping the empty list to itself, and a non-empty list | |
to some function applied to the head of the list and the result | |
of recursively processing the tail of the list in the same manner. | |
Abstracting this pattern gives the library function called map | |
map :: (a -> b) -> [a] -> [b] | |
map f [] = [] | |
map f (x:xs) = f x : map f xs | |
using which our two examples can now be defined more compactly: | |
inc = map (+1) | |
sqr = map (^2) | |
A simple evaluator | |
------------------ | |
Consider the following simple language of expressions that are | |
built up from integer values using a division operator: | |
data Expr = Val Int | Div Expr Expr | |
Such expressions can be evaluated as follows: | |
eval :: Expr -> Int | |
eval (Val n) = n | |
eval (Div x y) = eval x `div` eval y | |
However, this function doesn't take account of the possibility of | |
division by zero, and will produce an error in this case. In order | |
to deal with this explicitly, we can use the Maybe type | |
data Maybe a = Nothing | Just a | |
to define a "safe" version of division | |
safediv :: Int -> Int -> Maybe Int | |
safediv n m = if m == 0 then Nothing else Just (n `div` m) | |
and then modify our evaluator as follows: | |
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 | |
As in the previous section, we can observe a common pattern, namely | |
performing a case analysis on a value of a Maybe type, mapping Nothing | |
to itself, and Just x to some result depending upon x. (Aside: we | |
could go further and also take account of the fact that the case | |
analysis is performed on the result of an eval, but this would | |
lead to the more advanced notion of a monadic fold.) | |
How should this pattern be abstracted out? One approach would be | |
to observe that a key notion in the evaluation of division is the | |
sequencing of two values of a Maybe type, namely the results of | |
evaluating the two arguments of the division. Based upon this | |
observation, we could define a sequencing function | |
seqn :: Maybe a -> Maybe b -> Maybe (a,b) | |
seqn Nothing _ = Nothing | |
seqn _ Nothing = Nothing | |
seqn (Just x) (Just y) = Just (x,y) | |
using which our evaluator can now be defined more compactly: | |
eval (Val n) = Just n | |
eval (Div x y) = apply f (eval x `seqn` eval y) | |
where f (n,m) = safediv n m | |
The auxiliary function apply is an analogue of application for Maybe, | |
and is used to process the results of the two evaluations: | |
apply :: (a -> Maybe b) -> Maybe a -> Maybe b | |
apply f Nothing = Nothing | |
apply f (Just x) = f x | |
In practice, however, using seqn can lead to programs that manipulate | |
nested tuples, which can be messy. For example, the evaluation of | |
an operator Op with three arguments may be defined by: | |
eval (Op x y z) = apply f (eval x `seqn` (eval y `seqn` eval z)) | |
where f (a,(b,c)) = ... | |
Combining sequencing and processing | |
----------------------------------- | |
The problem of nested tuples can be avoided by returning of our | |
original observation of a common pattern: "performing a case analysis | |
on a value of a Maybe type, mapping Nothing to itself, and Just x to | |
some result depending upon x". Abstract this pattern directly gives | |
a new sequencing operator that we write as >>=, and read as "then": | |
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b | |
m >>= f = case m of | |
Nothing -> Nothing | |
Just x -> f x | |
Replacing the use of case analysis by pattern matching gives a | |
more compact definition for this operator: | |
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b | |
Nothing >>= _ = Nothing | |
(Just x) >>= f = f x | |
That is, if the first argument is Nothing then the second argument | |
is ignored and Nothing is returned as the result. Otherwise, if | |
the first argument is of the form Just x, then the second argument | |
is applied to x to give a result of type Maybe b. | |
The >>= operator avoids the problem of nested tuples of results | |
because the result of the first argument is made directly available | |
for processing by the second, rather than being paired up with the | |
second result to be processed later on. In this manner, >>= integrates | |
the sequencing of values of type Maybe with the processing of their | |
result values. In the literature, >>= is often called "bind", because | |
the second argument binds the result of the first. Note also that | |
>>= is just apply with the order of its arguments swapped. | |
Using >>=, our evaluator can now be rewritten as: | |
eval (Val n) = Just n | |
eval (Div x y) = eval x >>= (\n -> | |
eval y >>= (\m -> | |
safediv n m)) | |
The case for division can be read as follows: evaluate x and call | |
its result value n, then evaluate y and call its result value m, | |
and finally combine the two results by applying safediv. In | |
fact, the scoping rules for lambda expressions mean that the | |
parentheses in the case for division can freely be omitted. | |
Generalising from this example, a typical expression built using | |
the >>= operator has the following structure: | |
m1 >>= \x1 -> | |
m2 >>= \x2 -> | |
... | |
mn >>= \xn -> | |
f x1 x2 ... xn | |
That is, evaluate each of the expression m1,m2,...,mn in turn, and | |
combine their result values x1,x2,...,xn by applying the function f. | |
The definition of >>= ensures that such an expression only succeeds | |
(returns a value built using Just) if each mi in the sequence succeeds. | |
In other words, the programmer does not have to worry about dealing | |
with the possible failure (returning Nothing) of any of the component | |
expressions, as this is handled automatically by the >>= operator. | |
Haskell provides a special notation for expressions of the above | |
structure, allowing them to be written in a more appealing form: | |
do x1 <- m1 | |
x2 <- m2 | |
... | |
xn <- mn | |
f x1 x2 ... xn | |
Hence, for example, our evaluator can be redefined as: | |
eval (Val n) = Just n | |
eval (Div x y) = do n <- eval x | |
m <- eval y | |
safediv n m | |
Exercises: | |
o Show that the version of eval defined using >>= is equivalent to | |
our original version, by expanding the definition of >>=. | |
o Redefine seqn x y and eval (Op x y z) using the do notation. | |
Monads in Haskell | |
----------------- | |
The do notation for sequencing is not specific to the Maybe type, | |
but can be used with any type that forms a "monad". The general | |
concept comes from a branch of mathematics called category theory. | |
In Haskell, however, a monad is simply a parameterised type m, | |
together with two functions of the following types: | |
return :: a -> m a | |
(>>=) :: m a -> (a -> m b) -> m b | |
(Aside: the two functions are also required to satisfy some simple | |
properties, but we will return to these later.) For example, if | |
we take m as the parameterised type Maybe, return as the function | |
Just :: a -> Maybe a, and >>= as defined in the previous section, | |
then we obtain our first example, called the maybe monad. | |
In fact, we can capture the notion of a monad as a new class | |
declaration. In Haskell, a class is a collection of types that | |
support certain overloaded functions. For example, the class | |
Eq of equality types can be declared as follows: | |
class Eq a where | |
(==) :: a -> a -> Bool | |
(/=) :: a -> a -> Bool | |
x /= y = not (x == y) | |
The declaration states that for a type "a" to be an instance of | |
the class Eq, it must support equality and inequality operators | |
of the specified types. In fact, because a default definition | |
has already been included for /=, declaring an instance of this | |
class only requires a definition for ==. For example, the type | |
Bool can be made into an equality type as follows: | |
instance Eq Bool where | |
False == False = True | |
True == True = True | |
_ == _ = False | |
The notion of a monad can now be captured as follows: | |
class Monad m where | |
return :: a -> m a | |
(>>=) :: m a -> (a -> m b) -> m b | |
That is, a monad is a parameterised type "m" that supports return | |
and >>= functions of the specified types. The fact that m must be | |
a parameterised type, rather than just a type, is inferred from its | |
use in the types for the two functions. Using this declaration, | |
it is now straightforward to make Maybe into a monadic type: | |
instance Monad Maybe where | |
-- return :: a -> Maybe a | |
return x = Just x | |
-- (>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b | |
Nothing >>= _ = Nothing | |
(Just x) >>= f = f x | |
(Aside: types are not permitted in instance declarations, but we | |
include them as comments for reference.) It is because of this | |
declaration that the do notation can be used to sequence Maybe | |
values. More generally, Haskell supports the use of this notation | |
with any monadic type. In the next few sections we give some | |
further examples of types that are monadic, and the benefits | |
that result from recognising and exploiting this fact. | |
The list monad | |
-------------- | |
The maybe monad provides a simple model of computations that can | |
fail, in the sense that a value of type Maybe a is either Nothing, | |
which we can think of as representing failure, or has the form | |
Just x for some x of type a, which we can think of as success. | |
The list monad generalises this notion, by permitting multiple | |
results in the case of success. More precisely, a value of | |
[a] is either the empty list [], which we can think of as | |
failure, or has the form of a non-empty list [x1,x2,...,xn] | |
for some xi of type a, which we can think of as success. | |
Making lists into a monadic type is straightforward: | |
instance Monad [] where | |
-- return :: a -> [a] | |
return x = [x] | |
-- (>>=) :: [a] -> (a -> [b]) -> [b] | |
xs >>= f = concat (map f xs) | |
(Aside: in this context, [] denotes the list type [a] without | |
its parameter.) That is, return simply converts a value into a | |
successful result containing that value, while >>= provides a | |
means of sequencing computations that may produce multiple | |
results: xs >> f applies the function f to each of the results | |
in the list xs to give a nested list of results, which is then | |
concatenated to give a single list of results. | |
As a simple example of the use of th |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
data Expr = Val Int | Div Expr Expr | |
safediv :: Int -> Int -> Maybe Int | |
safediv n m = if m == 0 then Nothing else Just (n `div` m) | |
-- | |
-- Exercise: | |
-- Show that the version of eval defined using >>= is equivalent to our orginal version, by expanding the definition of >>= | |
-- | |
eval :: Expr -> Maybe Int | |
eval (Val n) = Just n | |
eval (Div x y) = eval x >>= (\n -> | |
eval y >>= (\m -> | |
safediv n m)) | |
-- *Main> eval (Div (Val 6) (Val 2)) | |
-- Just 3 | |
-- *Main> eval (Div (Val 6) (Val 0)) | |
-- Nothing | |
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 | |
-- *Main> eval' (Div (Val 6) (Val 2)) | |
-- Just 3 | |
-- *Main> eval' (Div (Val 6) (Val 0)) | |
-- Nothing | |
-- | |
-- Exercise: | |
-- Redefine seqn x y and eval (Op x y z) using the do notation | |
-- | |
seqn :: Maybe a -> Maybe b -> Maybe (a, b) | |
seqn Nothing _ = Nothing | |
seqn _ Nothing = Nothing | |
seqn (Just x) (Just y) = Just (x, y) | |
-- *Main> seqn (Just 1) (Just 3) | |
-- Just (1,3) | |
-- *Main> seqn (Just 1) Nothing | |
-- Nothing | |
seqn' :: Maybe a -> Maybe b -> Maybe (a, b) | |
seqn' a b = a >>= \x -> | |
b >>= \y -> | |
Just (x, y) | |
-- *Main> seqn' (Just 1) (Just 3) | |
-- Just (1,3) | |
-- *Main> seqn' (Just 1) Nothing | |
-- Nothing | |
seqn'' :: Maybe a -> Maybe b -> Maybe (a, b) | |
seqn'' a b = do x <- a | |
y <- b | |
Just (x, y) | |
-- *Main> seqn'' (Just 1) (Just 3) | |
-- Just (1,3)*Main> seqn'' (Just 1) Nothing | |
-- Nothing | |
-- sum three | |
data STExpr = STVal Int | SumThree STExpr STExpr STExpr | STNothing | |
evalST :: STExpr -> Maybe Int | |
evalST STNothing = Nothing | |
evalST (STVal n) = Just n | |
evalST (SumThree x y z) = do v1 <- evalST x | |
v2 <- evalST y | |
v3 <- evalST z | |
Just (v1 + v2 + v3) | |
-- *Main> evalST (SumThree (STVal 1) (STVal 2) (STVal 3)) | |
-- Just 6 | |
-- *Main> evalST (SumThree (STVal 1) STNothing (STVal 3)) | |
-- Nothing |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
data ST a = S (State -> (a, State)) | |
apply :: ST a -> State -> (a, State) | |
apply (S f) x = f x | |
instance Monad ST where | |
-- return :: a -> ST a | |
return x = S (\s -> (x, s)) | |
-- (>>=) :: ST a -> (a -> ST b) -> ST b | |
st >>= f = S (\s -> let (x, s') = apply st s in apply (f x) s') | |
-- | |
-- Tree example | |
-- | |
data Tree a = Leaf a | Node (Tree a) (Tree a) | |
type State = Int | |
fresh :: ST Int | |
-- fresh = S (\n -> (n, n+1)) | |
fresh = app (+1) | |
mlabel :: Tree a -> ST (Tree (a, Int)) | |
mlabel (Leaf x) = do n <- fresh | |
return (Leaf (x, n)) | |
mlabel (Node l r) = do l' <- mlabel l | |
r' <- mlabel r | |
return (Node l' r') | |
label :: Tree a -> Tree (a, Int) | |
--label t = fst (apply (mlabel t) 0) | |
label t = run (mlabel t) 0 | |
-- | |
-- Exercise: | |
-- Define a function app :: (State -> State) -> ST State, such that fresh can be redefined by fresh = app (+1). | |
-- | |
app :: (State -> State) -> ST State | |
app x = S (\s -> let s' = x s in (s, s')) | |
-- | |
-- Exercise: | |
-- Define a function run :: ST a -> State -> a, such that label can be redefined by label t = run (mlabel t) 0. | |
-- | |
run :: ST a -> State -> a | |
run (S st) = fst . st | |
-- helper | |
showTree :: (Show a) => Tree a -> String | |
showTree (Leaf x) = show x | |
showTree (Node l r) = "<" ++ showTree l ++ "|" ++ showTree r ++ ">" | |
-- | |
-- example session: | |
-- | |
-- | |
-- *Main> let tree = Node (Node (Leaf 'a') (Leaf 'b')) (Leaf 'c') | |
-- | |
-- | |
-- *Main> :t label tree | |
-- label tree :: Tree (Char, Int) | |
-- | |
-- | |
-- *Main> showTree $ label tree | |
-- "<<('a',0)|('b',1)>|('c',2)>" | |
-- | |
-- |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- | |
-- Exercise: | |
-- Define liftM and join more compactly by using >>=. | |
-- | |
liftM :: Monad m => (a -> b) -> m a -> m b | |
liftM f mx = do x <- mx | |
return (f x) | |
-- *Main> liftM length ["one", "two", "three"] | |
-- [3,3,5] | |
liftM' :: Monad m => (a -> b) -> m a -> m b | |
liftM' f mx = mx >>= return . f | |
-- *Main> liftM' length ["one", "two", "three"] | |
-- [3,3,5] | |
join :: Monad m => m (m a) -> m a | |
join mmx = do mx <- mmx | |
m <- mx | |
return m | |
-- *Main> join [[1,2],[3,4]] | |
-- [1,2,3,4] | |
join' :: Monad m => m (m a) -> m a | |
join' mmx = mmx >>= \mx -> mx | |
-- *Main> join' [[1,2],[3,4]] | |
-- [1,2,3,4] | |
-- | |
-- Exercise: | |
-- Explain the behaviour of sequence for the maybe monad | |
-- | |
-- *Main> sequence [(Just 3), (Just 2)] | |
-- Just [3,2] | |
-- *Main> sequence [(Just 3), (Just 2), Nothing] | |
-- Nothing | |
-- | |
-- | |
-- Exercise: | |
-- Define another monadic generalisation of map | |
-- | |
mapM' :: Monad m => (a -> m b) -> [a] -> m [b] | |
mapM' f xs = sequence $ map f xs | |
-- *Main> mapM' Just [1,2,3,4,5] | |
-- Just [1,2,3,4,5] | |
-- *Main> mapM' (\n -> if n < 4 then Just n else Nothing) [1,2,3,5] | |
-- Nothing | |
-- | |
-- Exercise: | |
-- Define a monadic generalisation for foldr | |
-- | |
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a | |
foldM f start = foldr (\y x -> | |
x >>= (\x' -> | |
f x' y)) | |
(return start) | |
-- *Main> foldM (\x y -> let sum = x + y in if sum < 20 then Just sum else Nothing) 0 [1,2,3,4,5] | |
-- Just 15 | |
-- *Main> foldM (\x y -> let sum = x + y in if sum < 20 then Just sum else Nothing) 10 [1,2,3,4,5] | |
-- Nothing | |
-- | |
-- foldM from the standard library - ARGH - it's so easy! ;-) | |
-- | |
-- foldM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a | |
-- foldM _ a [] = return a | |
-- foldM f a (x:xs) = f a x >>= \fax -> foldM f fax xs | |
-- |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- Exercise: | |
-- Show that the maybe monad satisfies equations (1), (2), and (3) | |
eq1 :: Int -> Maybe Int | |
eq1 n = return n >>= \n' -> return ((+1) n) | |
eq1satisfies = (eq1 3) == Just 4 | |
-- *Main> eq1satisfies | |
-- True | |
eq2 :: Maybe Int -> Maybe Int | |
eq2 m = m >>= return | |
eq2satisfies = (eq2 (Just 3)) == Just 3 | |
-- *Main> eq2satisfies | |
-- True | |
eq3a :: Maybe Int -> (Int -> Maybe Int) -> (Int -> Maybe Int) -> Maybe Int | |
eq3a mx f g = (mx >>= f) >>= g | |
eq3b mx f g = mx >>= (\x -> (f x >>= g)) | |
maybeAddOne n = Just (n + 1) | |
eq3satisfies = eq3a (Just 2) maybeAddOne maybeAddOne == eq3b (Just 2) maybeAddOne maybeAddOne | |
-- *Main> eq3satisfies | |
-- True | |
-- | |
-- An exercise | |
-- | |
data Expr a = Var a | Val Int | Add (Expr a) (Expr a) | |
instance Monad Expr where | |
-- return ::: a -> Expr a | |
return x = Var x | |
-- (>>=) :: Expr a -> (a -> Expr b) -> Expr b | |
(Var a) >>= f = undefined | |
(Val n) >>= f = undefined | |
(Add x y) >>= f = undefined | |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment