transformers tweak
[lambda.git] / monad_transformers.mdwn
1 [[!toc]]
2
3 Multi-layered monadic boxes
4 ===========================
5
6 So far, we've defined monads as single-layered boxes. Though in the Groenendijk, Stokhof, and Veltman homework, we had to figure out how to combine Reader, State, and Set monads in an ad-hoc way. In practice, one often wants to combine the abilities of several monads. Corresponding to each monad like Reader, there's a corresponding ReaderT **monad transformer**. That takes an existing monad M and wraps Readerish monad packaging around it. The way these are defined parallels the way the single-layer versions are defined. For example, here's the Reader monad:
7
8         (* monadic operations for the Reader monad *)
9
10         type 'a reader =
11                 env -> 'a;;
12         let unit (a : 'a) : 'a reader =
13                 fun e -> a;;
14         let bind (u: 'a reader) (f : 'a -> 'b reader) : 'b reader =
15                 fun e -> (fun a -> f a e) (u e);;
16
17 We've just beta-expanded the familiar `f (u e) e` into `(fun a -> f a
18 e) (u e)`. We did that so as to factor out the parts where any Reader monad is
19 being supplied as an argument to another function. That will help make some patterns that are coming up more salient.
20
21 That was the plain Reader monad. Now if we want instead to wrap some other monad M inside Readerish packaging. How could we do it?
22
23 Well, one way to proceed would be to just let values of the other monad M be the `'a` in your `'a reader`. Then you could apply `reader_bind` to get at the wrapped `'a M`, and then apply `M.bind` to get at *its* wrapped `'a`. This sometimes works. It's what we did in the hints to GSV assignment, where as we said, we "combined State and Set in an ad hoc way."
24
25 But there are two problems: (1) It's cumbersome having to work with *both* `reader_bind` and `M.bind`. It'd be nice to figure out some systematic way to connect the plumbing of the different monadic layers, so that we could have a *single* `bind` that took our `'a M_inside_Reader`, and sequenced it with a single `'a -> 'b M_inside_Reader` function. Similarly for `unit`. This is what the ReaderT monad transformer will let us do.
26
27 (2) For some combinations of monads, the best way to implement a Tish monadic wrapper around an inner M monad won't be equivalent to either an `('a m) t` or an `('a t) m`. It will be a tighter intermingling of the two. So some natural activities will remain out of reach until we equip ourselves to go beyond `('a m) t`s and so on.
28
29 What we want in general are monadic transformers. For example, a ReaderT transformer will be parameterized not just on the type of its innermost contents `'a`, but also on the monadic box `M` that wraps `'a`. It will make use of monad `M`'s existing operations `M.unit` and `M.bind`, together with the Reader patterns for unit and bind, to define a new monad ReaderT(M) that fuses the behavior of Reader and M.
30
31 To be clear: ReaderT isn't itself a monad. It's a kind of Readerish packaging (wrapping paper) that converts one monadic box M into another monadic box ReaderT(M).
32
33 Here's how it's implemented:
34
35         (* monadic operations for the ReaderT monadic transformer *)
36
37         (* We're not giving valid OCaml code, but rather something
38          * that's conceptually easier to digest.
39          * How you really need to write this in OCaml is more circuitous...
40          * see http://lambda.jimpryor.net/code/tree_monadize.ml
41          * and http://lambda.jimpryor.net/code/monads.ml
42          * for some details. *)
43
44         type 'a readerT(M) =
45                 env -> 'a M;;
46         (* this _happens_ also to be the type of an ('a M) reader
47          * but as we noted, you can't rely on that pattern always to hold *)
48
49         let unit (a : 'a) : 'a readerT(M) =
50                 fun e -> M.unit a;;
51
52         let bind (u : 'a readerT(M)) (f : 'a -> 'b readerT(M)) : 'b readerT(M) =
53                 fun e -> M.bind (u e) (fun a -> f a e);;
54
55 Notice the key differences: where before `unit` was implemented by a function that just returned `a`, now we
56 instead return `M.unit a`. Where before `bind` just supplied value `u e`
57 of type `'a reader` as an argument to a function, now we instead
58 `M.bind` the corresponding value to the function. Notice also the differences
59 in the types.
60
61 What is the relation between Reader and ReaderT? Well, suppose you started with the Identity monad:
62
63         type 'a identity = 'a;;
64         let unit (a : 'a) : 'a = a;;
65         let bind (u : 'a) (f : 'a -> 'b) : 'b = f u;;
66
67 and you used the ReaderT transformer to wrap the Identity monad inside Readerish packaging. What do you suppose you would get?
68
69 The relations between the State monad and the StateT monadic transformer are parallel:
70
71         (* monadic operations for the State monad *)
72
73         type 'a state =
74                 store -> ('a * store);;
75
76         let unit (a : 'a) : 'a state =
77                 fun s -> (a, s);;
78
79         let bind (u : 'a state) (f : 'a -> 'b state) : 'b state =
80                 fun s -> (fun (a, s') -> f a s') (u s);;
81
82 We've used `(fun (a, s') -> f a s') (u s)` instead of the more familiar `let (a, s') = u s in f a s'` in order to factor out the part where a value of type `'a state` is supplied as an argument to a function. Now StateT will be:
83
84         (* monadic operations for the StateT monadic transformer *)
85
86         type 'a stateT(M) =
87                 store -> ('a * store) M;;
88         (* notice this is not an ('a M) state *)
89
90         let unit (a : 'a) : 'a stateT(M) =
91                 fun s -> M.unit (a, s);;
92
93         let bind (u : 'a stateT(M)) (f : 'a -> 'b stateT(M)) : 'b stateT(M) =
94                 fun s -> M.bind (u s) (fun (a, s') -> f a s');;
95
96
97 Do you see the pattern? Where before `unit` was implemented by a function that returned an `'a * store` value, now we instead use `M.unit` to return an `('a * store) M` value. Where before `bind` supplied an `'a state` value `(u s)` as an argument to a function, now we instead `M.bind` it to that function.
98
99 Once again, what do you think you'd get if you wrapped StateT monadic packaging around an Identity monad?
100
101
102 We spell out all the common monads, their common dedicated operations (such as `lookup`- and `shift`-like operations for the Reader monad), and monad transformer cousins of all of these, in an OCaml [[monad library]]. Read the linked page for details about how to use the library, and some design choices we made. Our [[State Monad Tutorial]] gives some more examples of using the library.
103
104 When a T monadic layer encloses an inner M monad, the T's interface is the most exposed one. To use operations defined in the inner M monad, you'll have to "elevate" them into the outer T packaging. Haskell calls this operation `lift`, but we call it `elevate` because the term "lift" is already now too overloaded. In our usage, `lift` (and `lift2`) are functions that bring non-monadic operations into a monad; `elevate` brings monadic operations from a wrapped monad out into the wrapping.
105
106 Here's an example. Suppose `S` is an instance of a State monad:
107
108         # #use "path/to/monads.ml";;
109         # module S = State_monad(struct type store = int end);;
110
111 and `MS` is a MaybeT wrapped around `S`:
112
113         # module MS = Maybe_monad.T(S);;
114
115 Then if you want to use an `S`-specific monad like `puts succ` inside `MS`, you'll have to use `MS`'s `elevate` function, like this:
116
117         # MS.(...elevate (S.puts succ) ...)
118
119
120 We said that when T encloses M, you can rely on T's interface to be most exposed. That is intuitive. What you cannot also assume is that the implementing type has a Tish structure surrounding an Mish structure. Often it will be reverse: a ListT(Maybe) is implemented by a `'a list option`, not by an `'a option list`. Until you've tried to write the code to a monadic transformer library yourself, this will probably remain counter-intuitive. But you don't need to concern yourself with it in practise. Think of what you have as a ListT(Maybe); don't worry about whether the underlying implementation is as an `'a list option` or an `'a option list` or as something more complicated.
121
122 Notice from the code for StateT, above, that an `'a stateT(M)` is not an `('a M) state`; neither is it an `('a state) M`. The pattern by which we transform the types from a Blah monad to a BlahT monad transformer is:
123
124         't0                  --->  't0 M
125         't1 -> 't0           --->  't1 -> 't0 M
126         ('t1 -> 't0) -> 't0  --->  ('t1 -> 't0 M) -> 't0 M
127
128 Ken Shan's paper [Monads for natural language semantics](http://arxiv.org/abs/cs/0205026v1) (2001) discusses how to systematically move from some base monads to the corresponding monad transformers. But as he notes, his algorithm isn't the only one possible, and it only applies to monads whose type has a certain form. (Reader and State have that form; List for example doesn't.)
129
130 As best we know, figuring out how a monad transformer should be defined is still something of an art, not something that can be done mechanically. However, you can think that all of the art goes into deciding what StateT and so on should be; having figured that out, plain State would follow as the simple case where StateT is parameterized on the Identity monad.
131
132 Apart from whose interface is outermost, the behavior of a StateT(Maybe) and a MaybeT(State) will partly coincide. But in certain crucial respects they will diverge, and you need to think carefully about which behavior you want and what the appropriate layering is for your needs. Consider these examples:
133
134         # module MS = Maybe_monad.T(S);;
135         # module SM = S.T(Maybe_monad);;
136         # MS.(run (elevate (S.puts succ) >> zero () >> elevate S.get >>= fun cur -> unit (cur+10) )) 0;;
137         - : int option * S.store = (None, 1)
138         # MS.(run (elevate (S.puts succ) >> zero () >> elevate (S.put 5) )) 0;;
139         - : unit option * S.store = (None, 1)
140
141 Although we have a wrapped `None`, notice that the store (as it was at the point of failure) is still retrievable.
142
143         # SM.(run (puts succ >> elevate (Maybe_monad.zero ()) >> get >>= fun cur -> unit (cur+10) )) 0;;
144         - : ('a, int * S.store) Maybe_monad.result = None
145
146 When Maybe is on the inside, on the other hand, a failure means the whole computation has failed, and even the store is no longer available.
147
148 <!--
149         # ES.(run( elevate (S.puts succ) >> throw "bye" >> elevate S.get >>= fun i -> unit(i+10) )) 0;;
150         - : int Failure.error * S.store = (Failure.Error "bye", 1)
151         # SE.(run( puts succ >> elevate (Failure.throw "bye") >> get >>= fun i -> unit(i+10) )) 0;;
152         - : (int * S.store) Failure.result = Failure.Error "bye"
153         # ES.(run_exn( elevate (S.puts succ) >> throw "bye" >> elevate S.get >>= fun i -> unit(i+10) )) 0;;
154         Exception: Failure "bye".
155         # SE.(run_exn( puts succ >> elevate (Failure.throw "bye") >> get >>= fun i -> unit(i+10) )) 0;;
156         Exception: Failure "bye".
157 -->
158
159 Here's an example wrapping List around Maybe, and vice versa:
160
161         # module LM = List_monad.T(Maybe_monad);;
162         # module ML = Maybe_monad.T(List_monad);;
163         # ML.(run (plus (zero ()) (unit 20) >>= fun i -> unit (i+10)));;
164         - : ('_a, int) ML.result = [Some 30]
165
166 When List is on the inside, the failed results just get dropped and the computation proceeds without them.
167
168         # LM.(run (plus (elevate (Maybe_monad.zero ())) (unit 20) >>= fun i -> unit (i+10)));;
169         - : ('_a, int) LM.result = None
170
171 On the other hand, when Maybe is on the inside, failures abort the whole computation.
172
173 <!--
174         # EL.(run( plus (throw "bye") (unit 20) >>= fun i -> unit(i+10)));;
175         - : int EL.result = [Failure.Error "bye"; Failure.Success 30]
176         # LE.(run( plus (elevate (Failure.throw "bye")) (unit 20) >>= fun i -> unit(i+10)));;
177         - : int LE.result = Failure.Error "bye"
178         # EL.(run_exn( plus (throw "bye") (unit 20) >>= fun i -> unit(i+10)));;
179         Exception: Failure "bye".
180         # LE.(run_exn( plus (elevate (Failure.throw "bye")) (unit 20) >>= fun i -> unit(i+10)));;
181         Exception: Failure "bye".
182 -->
183
184 This is fun. Notice the difference it makes whether the second `plus` is native to the outer `List_monad`, or whether it's the inner `List_monad`'s `plus` elevated into the outer wrapper:
185
186         # module LL = List_monad.T(List_monad);;
187
188         # LL.(run(plus (unit 1) (unit 2) >>= fun i -> plus (unit i) (unit(10*i)) ));;
189         - : ('_a, int) LL.result = \[[1; 10; 2; 20]]
190         # LL.(run(plus (unit 1) (unit 2) >>= fun i -> elevate L.(plus (unit i) (unit(10*i)) )));;
191         - : ('_a, int) LL.result = [[1; 2]; [1; 20]; [10; 2]; [10; 20]]
192
193
194
195 Further Reading
196 ---------------
197
198 *       This is excellent, everyone should read: [Monad Transformers Step by Step](http://www.grabmueller.de/martin/www/pub/Transformers.pdf)
199
200 *       Read Part III of [All About Monads](http://web.archive.org/web/20071106232016/haskell.org/all_about_monads/html/introIII.html). This link is to an archived version, the main link to haskell.org seems to be broken. Some but not all of this site has been [absorbed into the Haskell wikibook](http://en.wikibooks.org/wiki/Haskell/Monad_transformers).
201
202
203 Tree Monads
204 ===========
205
206 Our [[monad library]] includes a `Tree_monad`, for binary, leaf-labeled trees. There are other kinds of trees you might want to monadize, but we took the name `Tree_monad` for this one. Like the Haskell [SearchTree](http://hackage.haskell.org/packages/archive/tree-monad/0.2.1/doc/html/src/Control-Monad-SearchTree.html#SearchTree) monad, our `Tree_monad` also incorporates an Optionish layer. (See the comments in our library code about `plus` and `zero` for discussion of why.)
207
208 So how does our `Tree_monad` behave? Simplified, its implementation looks something like this:
209
210         (* monadic operations for the Tree monad *)
211
212         type 'a tree =
213                 Leaf of 'a | Node of ('a tree) * ('a tree);;
214
215         let unit (a: 'a) : 'a tree =
216                 Leaf a;;
217
218         let rec bind (u : 'a tree) (f : 'a -> 'b tree) : 'b tree =
219             match u with
220             | Leaf a -> f a;;
221             | Node (l, r) ->
222                         let l' = bind l f in
223                         let r' = bind r f in
224                         Node (l', r')
225
226 Recall how `bind` works for the List monad. If you have a list:
227
228         let u = [1; 2; 4; 8];;
229
230 and a function `f` such that:
231
232         f 1 ~~> []
233         f 2 ~~> [2]
234         f 4 ~~> [2; 4]
235         f 8 ~~> [2; 4; 8]
236
237 then `list_bind u f` would be `concat [[]; [2]; [2; 4]; [2; 4; 8]]`, that is `[2; 2; 4; 2; 4; 8]`. It splices the lists returned by `f` into the corresponding positions in the original list structure. The `tree_bind` operation works the same way. If `f'` maps `2` to the tree `Leaf 2` and `8` to the tree `Node (Leaf 2, Node (Leaf 4, Leaf 8))`, then binding the tree `u` to `f'` will splice the trees returned by `f'` to the corresponding positions in the original structure:
238
239          u
240          .                    .
241         _|__  >>=  f' ~~>    _|__
242         |  |                 |  |
243         2  8                 2  .
244                                _|__
245                                |  |
246                                2  .
247                                  _|__
248                                  |  |
249                                  4  8
250
251 Except, as we mentioned, our implementation of the Tree monad incorporates an Optionish layer too. So `f' 2` should be not `Leaf 2` but `Some (Leaf 2)`. What if `f'` also mapped `1` to `None` and `4` to `Some (Node (Leaf 2, Leaf 4))`. Then binding the tree `Node (Leaf 1, Node (Leaf 2, Leaf 4))` to `f'` would delete thr branch corresponding to the original `Leaf 1`, and would splice in the results for `f' 2` and `f' 4`, yielding:
252
253          .                        
254         _|__  >>=  f' ~~>         
255         |  |                     
256         1  .                    .
257           _|__                 _|__
258           |  |                 |  |
259           2  4                 2  .
260                                  _|__
261                                  |  |
262                                  2  4
263
264 As always, the functions you bind an `'a tree` to need not map `'a`s to `'a tree`s; they can map them to `'b tree`s instead. For instance, we could transform `Node (Leaf 1, Node (Leaf 2, Leaf 4))` instead into `Node (Leaf "two", Node (Leaf "two", Leaf "four"))`.
265
266 As we [mention in the notes](/monad_library), our monad library encapsulates the implementation of its monadic types. So to work with it you have to use the primitives it provides. You can't say:
267
268         # Tree_monad.(orig_tree >>= fun a -> match a with
269             | 4 -> Some (Node (Leaf 2, Leaf 4))
270             | _ -> None);;
271         Error: This expression has type int Tree_monad.tree option
272                    but an expression was expected of type ('a, 'b) Tree_monad.m
273
274 You have to instead say something like this:
275
276         # Tree_monad.(orig_tree >>= fun a -> match a with
277             | 4 -> plus (unit 2) (unit 4)
278             | _ -> zero () );;
279         - : ('_a, int) Tree_monad.m = <abstr>
280
281
282
283 How is all this related to our tree\_monadize function?
284 -------------------------------------------------------
285
286 Recall our earlier definition of `tree_monadize`, specialized for the Reader monad:
287
288         let rec tree_monadize (f : 'a -> 'b reader) (t : 'a tree) : 'b tree reader =
289             match t with
290             | Leaf a -> reader_bind (f a) (fun b -> reader_unit (Leaf b))
291             | Node (l, r) -> reader_bind (tree_monadize f l) (fun l' ->
292                                reader_bind (tree_monadize f r) (fun r' ->
293                                  reader_unit (Node (l', r'))));;
294
295
296 (MORE...)
297