[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / docs / simple-monad.lhs
1 A Simple Country Boy's Guide to Monadic-Style Programming
2 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3
4 Forget the category theory, forget all the fancy talk, forget "monadic
5 I/O", forget Phil Wadler's papers!  Let's just do a little *plumbing*
6 in the monadic style, in plain-vanilla Haskell.
7
8 You can compile this guide as a Haskell module; I haven't put in
9 enough code to make it run or do anytning interesting.  Excuse me for
10 a moment, while I get some preliminaries out of the way...
11 \begin{code}
12 module Foo where
13
14 infixr 9 `thenFoo`, `thenFoo_` -- ignore me
15
16 data Foo = NullFoo | ConsFoo Int Foo -- assorted types, of little interest
17 type SwitchChecker = String -> Bool
18 type EnvA = [(String, Float)]
19 type NameSupply = Int
20 \end{code}
21
22 *** MOTIVATION *********
23
24 If you find that your Haskell functions are starting to carry around a
25 lot of baggage ..., e.g.,
26 \begin{code}
27 f :: EnvA -> SwitchChecker -> NameSupply -> Foo -> (Int, NameSupply)
28
29 f env sw_chkr names NullFoo = (0, names)
30
31 f env sw_chkr names (ConsFoo x xs)
32   = let
33         (x', names')  = f env sw_chkr names  xs
34     in
35     (x + x', names')
36 {-
37     `env' is some kind of environment;
38         what most people call "lookup tables".
39     `sw_chkr' is a function which, when presented with a
40         String, will tell you if that string was present
41         on the command line.
42     `names' is some kind of "name supply"; `f'
43     `f' returns a depleted name supply (2nd component of result).
44 -}
45 \end{code}
46
47 ...then it may be time to use monadic code to hide some of the mess!!
48
49 GRATUITOUS PLUMBING OF STATE MUST DIE.
50
51
52 *** SETTING UP THE MONAD MACHINERY *******
53
54 First, divide the things to be plumbed into:
55
56     * things that are only passed "downwards" through the function;
57       in the example above, the `env' and `sw_chkr' are such things;
58
59     * things that are "threaded" through the function; you want the
60       changed whatsit back from "down below"; `names' is such a thing.
61
62 Now, implement your monad; let's call it `FooM'; think of a `FooM
63 Wibble' as an *action* that, when performed, produces a `Wibble'.
64
65 \begin{code}
66 type FooM a =  EnvA             -- type of lookup-tbl being plumbed
67             -> SwitchChecker    -- type of switch looker-upper...
68             -> NameSupply       -- NameSupply going down...
69             -> (a,              -- result of the `FooM a' action
70                 NameSupply)     -- NameSupply that comes back...
71 \end{code}
72
73 (Note: in reality, it would be good practice to hide all this stuff
74 behind a clean interface, in another module.)
75
76 Let's write the basic operations on these `FooM a' guys:
77
78 \begin{code}
79 returnFoo :: a -> FooM a
80     -- make a `FooM thing' action from a `thing' value
81     -- [Phil W would call this `unitFoo']
82
83 thenFoo :: FooM a -> (a -> FooM b) -> FooM b
84     -- sequence two actions; the second uses the
85     -- result of the first
86     -- [Phil W would call this `bindFoo', or semi-colon :-]
87
88 thenFoo_ :: FooM a -> FooM b -> FooM b
89     -- sequence two actions; don't care about the
90     -- result of the first
91     -- [the name is a mnemonic for "... thenFoo \ _ -> ...]
92 \end{code}
93
94 They're implemented in the obvious way:
95 \begin{code}
96 returnFoo thing env sw_chkr ns = (thing, ns)
97
98 thenFoo action1 action2 env sw_chkr ns
99   = case (action1 env sw_chkr ns) of
100       (result1, ns1) -> action2 result1 env sw_chkr ns1
101
102 thenFoo_ action1 action2 env sw_chkr ns
103   = case (action1 env sw_chkr ns) of
104       (_{-boring result-}, ns1) -> action2 env sw_chkr ns1
105 \end{code}
106
107 All those are "pure plumbing".  We need a few "monadic functions" that
108 do something useful.
109
110 For example, you need to be able to "do a `FooM' action" and get the
111 answer back (along with the depleted NameSupply); for that, use...
112 \begin{code}
113 initFoo :: FooM a -> SwitchChecker -> NameSupply -> (NameSupply, a)
114
115 initFoo action sw_chkr ns
116   = case (action [] sw_chkr ns) of
117       (result, new_ns) -> (new_ns, result)
118         -- gratuitous order-swapping
119 \end{code}
120
121 You would then have a this-monad-specific set of functions to ``reach
122 down'' in the plumbing and use the env, switch-checker, etc., that are
123 being carried around.  Some examples might be:
124 \begin{code}
125 getNewName :: FooM Int
126
127 getNewName env sw_chkr ns = (ns, ns+1)
128
129 ------------
130
131 ifSwitchSet :: String -> FooM a -> FooM a -> FooM a
132
133 ifSwitchSet sw_to_chk then_ else_ env sw_chkr ns
134   = (if (sw_chkr sw_to_chk) then then_ else else_) env sw_chkr ns
135
136 ------------
137
138 lookupInEnv :: String -> FooM Float
139
140 lookupInEnv key env sw_chkr ns
141   = case [ v | (k, v) <- env, k == key ] of
142       []      -> error "lookupInEnv: no match"
143       (val:_) -> (val, ns)
144 \end{code}
145
146 *** USING THE MONAD MACHINERY *******
147
148 We now have everything needed to write beautiful (!) monadic code.  To
149 remind you of the basic "monadic" functions at our disposal:
150
151 \begin{verbatim}
152 returnFoo :: a -> FooM a
153 thenFoo :: FooM a -> (a -> FooM b) -> FooM b
154 thenFoo_ :: FooM a -> FooM b -> FooM b
155 initFoo :: FooM a -> SwitchChecker -> NameSupply -> (NameSupply, a)
156
157 getNewName :: FooM Int
158 ifSwitchSet :: String -> FooM a -> FooM a -> FooM a
159 lookupInEnv :: String -> FooM Float
160 \end{verbatim}
161
162 Before going on: there are a few plumbing things that aren't
163 essential, but tend to be useful.  They needn't be written at the
164 "bare-bones" level; they show the use of `returnFoo' and `thenFoo'.
165 \begin{code}
166 mapFoo :: (a -> FooM b) -> [a] -> FooM [b]
167
168 mapFoo f []     = returnFoo []
169 mapFoo f (x:xs)
170   = f x         `thenFoo` \ r  ->
171     mapFoo f xs `thenFoo` \ rs ->
172     returnFoo (r:rs)
173
174 mapAndUnzipFoo  :: (a -> FooM (b,c))   -> [a] -> FooM ([b],[c])
175
176 mapAndUnzipFoo f [] = returnFoo ([],[])
177 mapAndUnzipFoo f (x:xs)
178   = f x                 `thenFoo` \ (r1,  r2)  ->
179     mapAndUnzipFoo f xs `thenFoo` \ (rs1, rs2) ->
180     returnFoo (r1:rs1, r2:rs2)
181 \end{code}
182
183 You should read
184
185     f x `thenFoo` \ r -> ...
186
187 as
188
189     "do `f' with argument `x', giving result `r'".
190
191 If you wanted, you could do really horrible things with the C
192 pre-processor (GHC and HBC let you do this...):
193 \begin{verbatim}
194 #define RETN returnFoo
195 #define BIND {--}
196 #define _TO_ `thenFoo` \ {--}
197
198 mapFoo f [] = RETN []
199 mapFoo f (x:xs)
200   = BIND (f x)         _TO_ r  ->
201     BIND (mapFoo f xs) _TO_ rs ->
202     RETN (r:rs)
203 \end{verbatim}
204
205 *** USING THE MONAD MACHINERY, FOR REAL *******
206
207 We can finally re-write our `f' function in a "monadic style" (except
208 I'll call it `g'), using the functions above.
209 \begin{code}
210 g :: Foo -> FooM Int
211     -- `g' has the same arguments as `f' (really), but in a different
212     -- order: just unravel the type synonyms
213
214 g NullFoo = returnFoo 0
215
216 g (ConsFoo x xs)
217   = g xs    `thenFoo` \ x' ->
218     returnFoo (x + x')
219 \end{code}
220
221 LOOK, MOM, NO GRATUITOUS PLUMBING OF STATE!
222
223 OK, `g' shows how much the monadic style tidies up the plumbing, but
224 it is really boring---it doesn't use any of the functions we defined
225 earlier.  Here's a function that does:
226 \begin{code}
227 h :: Int -> FooM Integer
228
229 h x
230   = getNewName  `thenFoo_` -- ignore that one...
231     getNewName  `thenFoo`  \ int_name ->
232
233     mapAndUnzipFoo zwonk [int_name ..]
234                 `thenFoo` \ (some_nums, more_nums) ->
235
236     ifSwitchSet "-beat-hbc" (
237         returnFoo (toInteger (some_nums !! 6) + 42)
238
239     ) {-else-} (
240         lookupInEnv "-ghc-is-cool"  `thenFoo` \ ghc_float ->
241         returnFoo (toInteger (truncate ghc_float))
242     )
243   where
244     zwonk :: Int -> FooM (Int, Int)
245     zwonk i = returnFoo (i, x*i)
246 \end{code}
247
248 *** CONCLUSION *******
249
250 Ordinary Haskell programming, but in a "monadic style", is a good way
251 to control the plumbing of state through your code.
252
253 I have left out lots and lots of Neat Things you can do with monads --
254 see the papers for more interesting stuff.  But 99% of the monadic
255 code you're likely to write or see will look like the stuff in here.
256
257 Comments, suggestions, etc., to me, please.
258
259 Will Partain
260 partain@dcs.glasgow.ac.uk
261
262 % compile with:
263 %   ghc -cpp <other-flags> Foo.lhs
264 %   hbc -M <other-flags> Foo.lhs