A Schemer’s View of Monads Partial Draft Adam C. Foltzer & Daniel P. Friedman April 21, 2011 Lecture 1: The State Monad This tutorial lecture is based on the first four pages of “Notions of Computation and Monads” by Eugenio Moggi, who took the idea of monads from category theory and pointed out its relevance to programming languages.1 Everything in these two lectures will simply be purely functional code. There will be no set!s; there will be one call/cc to help motivate an example in the second lecture; and there will be lots of λs and lets. The only requirement is understanding functions as values. The goal of these two lectures is to teach how monads work. It impedes understanding if we concern ourselves with a lot of details or sophisticated built-in tools, so we use only a very small subset of Scheme to expose the relevant ideas. There is one program written in continuation-passing style that shows one way of computing two values in one pass, but it is not important to understand the program. In fact, it is only necessary to notice a single occurrence of the symbol +. There is also the continuation monad, explained toward the end of the second lecture in section 8, and here, it might help to have some familiarity with first-class continuations. 1 Prologue: The Identity Monad To start, we will walk through two typical Scheme programming challenges, and then show how they naturally give rise to a monad. 1.1 Recreating begin Our first challenge is to recreate the behavior of Scheme’s begin using only λ and function application. > (begin (printf "One\n") (printf "Two\n")) One Two In this example, begin enforces the order in which the two printf expressions are evaluated. To get the same behavior just from λ and application, we must take advantage of the fact that Scheme is a call-by-value language. That is, the arguments to a function are always evaluated before the body of the function. We need to arrange our expression so that (printf "One\n") is an argument to a function that contains (printf "Two\n"). 1 See http://www.disi.unige.it/person/MoggiE/publications.html. 1 PARTIAL DRAFT > ((λ ( ) (printf "Two\n")) (printf "One\n")) One Two Success! Note that there’s nothing special about ; it simply means that we do not care about the value of (printf "One\n"). We only care that it gets evaluated for its printing effect. This code would look nicer if the evaluation order of our statements read from left-to-right, as with begin. The only reason our example reads the other way is the order of function application: (function argument). To get the order we want, we can define a backwards function application: (define mybegin (λ (x f ) (f x ))) > (mybegin (printf "One\n") (λ ( ) (printf "Two\n"))) One Two This is an improvement. How about printing a third string? > (mybegin (printf "One\n") (λ ( ) (mybegin (printf "Two\n") (λ ( ) (printf "Three\n"))))) One Two Three 1.2 Recreating let Our next challenge is to recreate the behavior of Scheme’s scheme—let— using the same toolkit of λ and function application. Again, we start with a simple example. > (let ([x 5]) (+ x 3)) 8 Nesting let in this way enforces the order of evaluation similarly to begin. Here, 5 must be evaluated before (+ x 3). We can start by applying the same basic structure as our begin example. ((λ ( ) (+ x 3)) 5) This isn’t quite right, though, since let does more than begin. Rather than throwing away the value of, for example, (printf "One\n") by binding it to an unused variable , we need to evaluate 5 and then bind it to x : > ((λ (x ) (+ x 3)) 5) 8 Let’s use the same trick we used for mybegin to make this code look nicer. (define mylet (λ (x f ) (f x ))) > (mylet 5 (λ (x ) (+ x 3))) 8 We can also work easily with larger examples. > (mylet 5 (λ (x ) (mylet x (λ (y) (+ x y))))) 10 2 PARTIAL DRAFT 1.3 The programmable semicolon Why, then, bother with two names for the same function? After all, the definitions of mybegin and mylet are identical. Let’s call these what they really are, which is bindidentity . (define bindidentity (λ (x f ) (f x ))) With a definition for bindidentity , we nearly have a monad; we also need a function unitidentity . Loosely speaking, unitM is a function that brings a value into the world of a monad M in a natural way. The identity monad’s world is simply the world of Scheme values, so the natural choice is the identity function. (define unitidentity (λ (a) a)) Our examples are easily translated into the identity monad by replacing mylet and mybegin with bindidentity , and by bringing our Scheme values (trivially) into the identity monad with unitidentity . > (bindidentity (unitidentity (printf "One\n")) (λ ( ) (bindidentity (unitidentity (printf "Two\n")) (λ ( ) (unitidentity (printf "Three\n")))))) One Two Three > (bindidentity (unitidentity 5) (λ (x ) (unitidentity (+ x 3)))) 8 > (bindidentity (unitidentity 5) (λ (x ) (bindidentity (unitidentity x ) (λ (y) (unitidentity (+ x y)))))) 10 The identity monad by itself isn’t terribly useful. After all, we can write these examples more concisely with begin and let. What we’ve done, though, is provide a hook into how we evaluate expressions in sequence; bindM is a programmable semicolon2 . bindidentity encodes a very basic notion of sequencing, ”do this, then do that”. The way we have structured the code that uses bindidentity allows us to switch to more complex notions of sequencing simply by swapping bindidentity for a differently-programmed semicolon. 2 The State Monad Here is a predicate even-length? which takes a list ls, and then returns #t if the length of ls is even, and #f otherwise. (define even-length? (λ (ls) (cond ((null? ls) #t) (else (not (even-length? (cdr ls))))))) > (even-length? ’(1 2 3 4)) #t 2 See ”Real World Haskell” by Bryan O’Sullivan, http://book.realworldhaskell.org/read/monads.html#id642960 3 Don Stewart, and John Goerzen PARTIAL DRAFT Suppose we want to rewrite even-length? using store-passing style. We add the store as an argument s and give it the initial value #t. Each time we recur, we negate the value of s, so that we are left with the correct answer in s at the end of the computation. (define even-length? sps (λ (ls s) (cond [(null? ls) s] [else (even-length? sps (cdr ls) (not s))]))) > (even-length? sps ’(1 2 3 4) #t) #t The state monad allows us to write programs that use state without the overhead of adding an extra argument like s to all of our functions. It accomplishes this without set! or its relatives, providing an illusion of a mutable variable with purely-functional code. Here is even-length? state , which uses the state monad to replace the extra argument to even-length? sps . (define even-length? state (λ (ls) (cond ((null? ls) (unitstate ’ )) (else (bindstate (λ (s) ‘( . ,(not s))) (λ ( ) (even-length? state (cdr ls)))))))) > ((even-length? state ’(1 2 3 4)) #t) ( . #t) This resulting value is unusual. Where even-length? and even-length? sps return a boolean value, evenlength? state returns a pair whose cdr is the boolean value we expect, and whose car is the symbol . Running a computation in the state monad always returns a pair of a natural value and final state of the computation. For even-length? state , we only care about the final state, so we use throughout the program as a convention to indicate that the natural value is irrelevant. More unusual than the resulting value are the two new functions that appear in this definition: unitstate and bindstate . These functions comprise the state monad. (define unitstate (λ (a) (λ (s) ‘(,a . ,s)))) unitstate takes a natural value a and returns a trivial computation in the state monad. When passed a state s, this trivial computation returns a pair of a and s, both unchanged. 4 PARTIAL DRAFT (define bindstate (λ (ma sequel ) (λ (s) (let ((p (ma s))) (let ((â (car p)) (ŝ (cdr p))) (let ((mb (sequel â))) (mb ŝ))))))) bindstate composes two state monad computations into a single computation. This composition requires that any changes to the state made by the first computation be visible to the second. To accomplish this, bindstate passes an initial state s into the first computation ma, which returns a pair (â . ŝ), the natural value and resulting state of running ma. Then, it passes â to the sequel function, which returns the second computation mb. With mb in hand, all that remains is to pass the intermediate state ŝ to mb, yielding the result of the composed computation. even-length? state doesn’t use the full power these functions give us since it always ignores the natural value. Let’s look at an example that uses both the state and the natural value. The task is to take a nested (any depth) list of integers and return as the natural value the list with all even numbers removed. The state of the computation will be a running tally of the even numbers that have been deleted, so that when the computation finishes, it will be the count of all the even numbers in the original list. We call this function remberevens Xcountevens. The cross X indicates that the function returns an eXtra value. Before we move on to a monadic definition of remberevens Xcountevens, let’s again look at a simple, direct-style definition. We start with a “driver” procedure, remberevens Xcountevens 2pass , that calls off to two helpers, remberevens direct and countevens direct . (define remberevens Xcountevens 2pass (λ (l ) ‘(,(remberevens direct l ) . ,(countevens direct l )))) (define remberevens direct (λ (l ) (cond ((null? l ) ’()) ((pair? (car l )) (cons (remberevens direct (car l )) (remberevens direct (cdr l )))) ((or (null? (car l )) (odd? (car l ))) (cons (car l ) (remberevens direct (cdr l )))) (else (remberevens direct (cdr l )))))) (define countevens direct (λ (l ) (cond ((null? l ) 0) ((pair? (car l )) (+ (countevens direct (car l )) (countevens direct (cdr l )))) ((or (null? (car l )) (odd? (car l ))) (countevens direct (cdr l ))) (else (add1 (countevens direct (cdr l ))))))) > (remberevens Xcountevens 2pass ’(2 3 (7 4 5 6) 8 (9) 2)) ((3 (7 5) (9)) . 5) 5 PARTIAL DRAFT The remberevens Xcountevens 2pass solution works, but is inefficient: it processes the list l twice. There is a well-known way to get the same answer, and yet process the list once, but the solution requires that we transform the code into continuation-passing style. (define remberevens Xcountevens cps (λ (l k ) (cond ((null? l ) (k ‘(() . 0))) ((pair? (car l )) (remberevens Xcountevens cps (car l ) (λ (pa) (remberevens Xcountevens cps (cdr l ) (λ (pd ) (k ‘(,(cons (car pa) (car pd )) . ,(+ (cdr pa) (cdr pd ))))))))) ((or (null? (car l )) (odd? (car l ))) (remberevens Xcountevens cps (cdr l ) (λ (p) (k ‘(,(cons (car l ) (car p)) . ,(cdr p)))))) (else (remberevens Xcountevens cps (cdr l ) (λ (p) (k ‘(,(car p) . ,(add1 (cdr p)))))))))) > (remberevens Xcountevens cps ’(2 3 (7 4 5 6) 8 (9) 2) (λ (p) p)) ((3 (7 5) (9)) . 5) Next we transform the direct-style remberevens direct into monadic style. The fourth clause is a tail call, so it remains unchanged. In the third clause, we take the nontail call (with simple arguments) and make it the first argument to bindstate . (bindstate (remberevens direct (cdr l )) . . . ) The context around the nontail call goes into the “. . . ” and we must have a variable to bind the natural value of the call to (remberevens direct (cdr l )), so let’s call it d . (bindstate (remberevens direct (cdr l )) (λ (d ) . . . )) The (λ (d ) . . . ) here is the sequel argument to bind, and since bindstate ’s job is to thread the state from the first computation to the computation returned by the sequel , we need not worry at all about the state at this point. Next, if we have a simple expression (one without a recursive function call) like (cons (car l ) d ), then to monadify it, we use unitstate around the simple expression. (bindstate (remberevens direct (cdr l )) (λ (d ) (unitstate (cons (car l ) d )))) Consider the second clause. Here we have two nontail (recursive) calls (with simple arguments), so we have to sequence them. (bindstate (remberevens direct (car l )) (λ (a) . . . )) In the body of (λ (a) . . . ) we make the next call. (bindstate (remberevens direct (car l )) (λ (a) (bindstate (remberevens direct (cdr l )) (λ (d ) . . . )))) 6 PARTIAL DRAFT Finally, we have unnested the recursive calls on both the car and the cdr , and all that’s left is to (cons a d ), which is simple. Once again we wrap the simple expression using unit.3 (bindstate (remberevens direct (car l )) (λ (a) (bindstate (remberevens direct (cdr l )) (λ (d ) (unitstate (cons a d )))))) The first clause is simple: we simply pass ’() to unitstate , and we have our result. (define remberevens (λ (l ) (cond ((null? l ) (unitstate ’())) ((pair? (car l )) (bindstate (remberevens (car l )) (λ (a) (bindstate (remberevens (cdr l )) (λ (d ) (unitstate (cons a d ))))))) ((or (null? (car l )) (odd? (car l ))) (bindstate (remberevens (cdr l )) (λ (d ) (unitstate (cons (car l ) d ))))) (else (remberevens (cdr l )))))) Of course, all we’ve dealt with so far is remberevens, and what we really wanted was remberevens Xcountevens. It would seem that we’ve only done half of our job. However, the beauty of the state monad is that we are almost done. Let’s change the name of the function to remberevens Xcountevens almost and see just how far off we are. ∗ 3 The nested calls to bind state could be made to look simpler with a macro dostate , reminiscent of Haskell’s do and Scheme’s let∗ . (define-syntax do∗state (syntax-rules () (( () body) body) (( ((a0 ma0 ) (a ma) . . . ) body) (bindstate ma0 (λ (a0 ) (do∗state ((a ma) . . . ) body)))))) (do∗state ((a (remberevens direct (car l))) (d (remberevens direct (cdr l)))) (unitstate (cons a d))) 7 PARTIAL DRAFT (define remberevens Xcountevens almost (λ (l ) (cond ((null? l ) (unitstate ’())) ((pair? (car l )) (bindstate (remberevens Xcountevens almost (car l )) (λ (a) (bindstate (remberevens Xcountevens almost (cdr l )) (λ (d ) (unitstate (cons a d ))))))) ((or (null? (car l )) (odd? (car l ))) (bindstate (remberevens Xcountevens almost (cdr l )) (λ (d ) (unitstate (cons (car l ) d ))))) (else (remberevens Xcountevens almost (cdr l )))))) First, what does (remberevens Xcountevens almost l ) return? It returns a function that takes a state and returns a pair of values, the natural value that one might return from a call to (remberevens direct l ) and the state, which is the number of even numbers that have been removed. Here is a test of remberevens Xcountevens almost . > ((remberevens Xcountevens almost ’(2 3 (7 4 5 6) 8 (9) 2)) 0) ((3 (7 5) (9)) . 0) What is 0 doing in the test? It is the initial value of the state s. What happens when the list of numbers is empty? Then, we return (unitstate ’()), which is a function (λ (s) ‘(() . ,s)), by substituting () for a in the body of unitstate . Then 0 is substituted for s, which yields the pair (() . 0). But, our answer is almost correct, since the only part that is wrong is the count. When should we be counting? When we know we have an even number in (car l ). So, let’s look at that else clause again. (remberevens Xcountevens almost (cdr l )) How can we revise this expression to fix the bug? This is a tail call, so we move the call into the body of a sequel. (bindstate . . . (λ ( ) (remberevens Xcountevens almost (cdr l )))) Then we manufacture a state monad computation that modifies the state. In even-length? state , (λ (s) ‘( . ,(not s))) is the computation we use to negate the state, which in that computation was a boolean value.4 Here, we instead want to increment the state that is an integer. We don’t care about the natural value of incrementing the state for the same reason we wouldn’t care about the value of (set! s (add1 s)), so we’ll again use for both the natural value and the variable that it will be bound to in the sequel . (bindstate (λ (s) ‘( . ,(add1 s))) (λ ( ) (remberevens Xcountevens almost (cdr l )))) Since the s coming into this computation is the current count, our computation yields the state (add1 s), and the else clause is finished. The code is now correct, so we drop the almost subscript from the name. 4 Like the bodies of unit state and bindstate , state monad computations are of the form (λ (s) body) where body evaluates to a pair. The same principle applies to the sequel, which is of the form (λ (a) mb) where mb evaluates to a state monad computation. 8 PARTIAL DRAFT (define remberevens Xcountevens (λ (l ) (cond ((null? l ) (unitstate ’())) ((pair? (car l )) (bindstate (remberevens Xcountevens (car l )) (λ (a) (bindstate (remberevens Xcountevens (cdr l )) (λ (d ) (unitstate (cons a d ))))))) ((or (null? (car l )) (odd? (car l ))) (bindstate (remberevens Xcountevens (cdr l )) (λ (d ) (unitstate (cons (car l ) d ))))) (else (bindstate (λ (s) ‘( . ,(add1 s))) (λ ( ) (remberevens Xcountevens (cdr l )))))))) > ((remberevens Xcountevens ’(2 3 (7 4 5 6) 8 (9) 2)) 0) ((3 (7 5) (9)) . 5) Let’s think about the earlier definition in continuation-passing style. Both programs compute the correct answer, but they are doing so in very different ways. To show that this is the case, let’s trace the execution of the add1 and + operators as we run each version of the program. Here’s what happens for remberevens Xcountevens cps : > (remberevens Xcountevens cps ’(2 3 (7 4 5 6) 8 (9) 2) (λ (p) p)) |(add1 0) |1 |(add1 1) |2 |(add1 0) |1 |(+ 0 1) |1 |(add1 1) |2 |(+ 2 2) |4 |(add1 4) |5 ((3 (7 5) (9)) . 5) As we can see from the execution trace, remberevens Xcountevens cps computes the number 5 by computing sub-answers for the various sub-lists in the input, then combining the sub-answers with +. 9 PARTIAL DRAFT Let’s look at a trace of the monadic version, remberevens Xcountevens: > ((remberevens Xcountevens ’(2 3 (7 4 5 6) 8 (9) 2)) 0) |(add1 0) |1 |(add1 1) |2 |(add1 2) |3 |(add1 3) |4 |(add1 4) |5 ((3 (7 5) (9)) . 5) Now the results of calls to add1 are following a predictable pattern, and + is never used at all! Instead of building up answers from sub-answers, as we see happening in the trace of remberevens Xcountevens cps , this version looks like we’re incrementing a counter. In fact, the computation that takes place is rather like what would have happened if we had created a global variable counter , initialized it to 0, and simply run (set! counter (add1 counter )) five times. But we do it all without having to use set!. Instead, the state monad provides us with the illusion of a mutable global variable. This is an extremely powerful idea. We can now write programs that provide a faithful simulation of effectful computation without actually performing any side effects—that is, we get the usual benefits of effectful computation without the usual drawbacks. A final observation on the state monad is that the auxiliary function (λ (s) ‘( . ,(add1 s))), which contains no free variables, could have been given a global name, say incrstate . (define incrstate (λ (s) ‘( . ,(add1 s)))) We might also recognize that it’s common to apply arbitrary functions to the state rather than just add1 , such as (λ (s) ‘( . ,(not s))) from even-length? state . It is straightforward to define these both in terms of updatestate , (define updatestate (λ (f ) (λ (s) ‘( . ,(f s))))) (define incrstate (updatestate add1 )) (define negatestate (updatestate not)) but then the relationship between the ma and sequel in a call to bindstate . ,(add1 s))) ⇐= ma (λ (s) ‘( ⇓ (λ ( ) . . . ) ⇐= sequel would not be as clear. The pure value, the symbol , in the car of the pair returned when a state is passed to a ma is bound to the formal parameter, , of the sequel. In addition to threading the state through the two computations, making this binding occur is how bindstate composes two computations.5 5 We blithely use , but it is not an odd or even integer. In Scheme, however, we have no real need to distinguish these types. We merely need to agree that we don’t care about the fact that we are binding a useless value to a useless variable. Also, if we think about unitstate and bindstate as methods of some class C , we could imagine another class that inherits C and includes the incrstate method, but this is just packaging. 10 PARTIAL DRAFT Exercise: In remberevens Xcountevens, the increment takes place before the tail recursive call, but we are free to reorder these events. Implement this reordered-events variant by having the body of the sequel become the first argument to bindstate and make the appropriate adjustments to the sequel . Is this new first argument to bindstate a tail call? Exercise: Define remberevens Xmaxseqevens, which removes all the evens, but while it does that, it also returns the length of the longest sequence of even numbers without an odd number. There are two obvious ways to implement this function; try to implement them both. Hint: Consider holding more than a single value in the state. 3 Deriving the State Monad If we take the code for remberevens Xcountevens and replace the definitions of unitstate and bindstate by their definitions, opportunities for either (let ((x e)) body) or equivalently ((λ (x ) body) e) exist for substituting e for x in body. If we know that x occurs in body just once, then these are correctness and efficiency (or better) preserving transformations. These transformations (all thirty-six) are in the appendix, worked out in detail, but, the result is the code in store-passing style, where a store is an argument passed in and out of every recursive function call. The resulting code is what we might have written had we not known of the state monad. (define remberevens Xcountevens sps (λ (l s) (cond ((null? l ) ‘(() . ,s)) ((pair? (car l )) (let ((p (remberevens Xcountevens sps (car l ) s))) (let ((p̂ (remberevens Xcountevens sps (cdr l ) (cdr p)))) ‘(,(cons (car p) (car p̂)) . ,(cdr p̂))))) ((or (null? (car l )) (odd? (car l ))) (let ((p (remberevens Xcountevens sps (cdr l ) s))) ‘(,(cons (car l ) (car p)) . ,(cdr p)))) (else (let ((p (remberevens Xcountevens sps (cdr l ) s))) ‘(,(car p) . ,(add1 (cdr p)))))))) > (remberevens Xcountevens sps ’(2 3 (7 4 5 6) 8 (9) 2) 0) ((3 (7 5) (9)) . 5) We can also start from remberevens Xcountevens sps and derive unitstate and bindstate , since each correctnesspreserving transformation is invertible. This ends the first monad lecture. In the second lecture, we will present various other monads and how one might use them. 11 PARTIAL DRAFT Lecture 2: Other monads 4 Monads in a Nutshell Each monad is a pair of functions, unitM and bindM , that cooperate to do some rather interesting things. A particular unitM , bindM pair is a monad if the following monadic laws hold: • (bindM m unitM ) = m • (bindM (unitM x ) f ) = (f x ) • (bindM (bindM m f ) g) = (bindM m (λ (x ) (bindM (f x ) g))) Once we are at the point of developing our own monads, we will have to prove that the monadic laws hold for our proposed unitM and bindM , but for now, we will only be dealing with known monads. If we wish to convince ourselves that a monad is truly a monad, we’ll need to prove these laws. 5 Types and Shapes Consider three types of values: Pure values, denoted by a and b; monadic expressions, denoted by ma and mb; and functions, denoted by sequelM , that take a pure value a and return a monadic value mb. The unitM function is “shaped” something like a sequelM , and bindM takes two arguments, a sequelM and a ma, and returns a mb. We can therefore write down the types of unitM and bindM as follows. sequelM = a → mb unitM : a → ma bindM : ma → sequelM → mb; or ma → (sequelM → mb) Here, the first line simply tells us that the type sequelM is an abbreviation for the type a → mb. The following two lines tell us the types of the expressions unitM and bindM , respectively. We can read the colon, :, as “has the type”. From the monadic laws, we know that the expression (bindM m unitM ) is allowed, even though bindM seems to want a value of type sequelM as its first argument. Therefore, we know that unitM and a sequelM must have a similar shape. They both consume a pure value a and return either a ma or a mb. Furthermore, (unitM a) and (bindM ma sequelM ) both return the same shape, a ma or mb, respectively. 12 PARTIAL DRAFT In this lecture we introduce several more monads by “instantiating”, or replacing, the subscripted M and the m in ma and mb with a particular monad. In order for a particular choice of M to serve as a monad, we must define a particular pair of unitM and bindM that satisfies the monadic laws. 6 The List Monad Here is the list monad. (define unitlist (λ (a) ‘(,a))) ; ⇐= This list is a ma. (define bindlist (λ (ma sequel ) (mapcan sequel ma))) (define mapcan (λ (f ls) (cond ((null? ls) ’()) (else (append (f (car ls)) (mapcan f (cdr ls))))))) We know that a ma is a list of natural values, so each (sequel a) returns a list of natural values mb, thus the result of mapcan will also be a list of natural values. We will find the auxiliaries mzero list and mplus list quite useful. In general, mzeroM represents a computation with no answer in the monad M , and mplusM combines the answers from two computations. Not all monads have these notions; unitM and bindM are the only definitions common to all monads. (define mzero list ’()) (define mplus list append ) Consider this example (http://www.haskell.org/all about monads/html/listmonad.html) from Jeff Newburn’s tutorial. “The canonical example of using the List monad is for parsing ambiguous grammars. The example below shows just a small example of parsing data into hex values, decimal values, and words containing only alphanumeric characters. Note that hexadecimal digits overlap both decimal digits and alphanumeric characters, leading to an ambiguous grammar. "dead" is both a valid hex value and a word, for example, and "10" is both a decimal value of 10 and a hex value of 16.” ("10" is also an alphanumeric word.) In the definition of parse-c∗ below, we first create the three specialized parsers that take a pure tagged value and a new character. Then, we define the function that takes a tagged value and a list of characters. The same character is passed to these three defined parsers along with a tagged value. Each parser returns a ma, which are then formed into a list by combining the mas together using mplus list . (define parse-c∗ (λ (a c∗ ) (cond ((null? c∗ ) (unitlist a)) (else (bindlist (mplus list (parse-hex-digit a (car c∗ )) (parse-dec-digit a (car c∗ )) (parse-alphanumeric a (car c∗ ))) (λ (a) (parse-c∗ a (cdr c∗ )))))))) 13 PARTIAL DRAFT (define char-hex? (λ (c) (or (char-numeric? c) (char ≤? #\a c #\f)))) (define char-hex→integer/safe (λ (c) (− (char→integer c) (if (char-numeric? c) (char→integer #\0) (− (char→integer #\a) 10))))) (define parse-hex-digit (λ (a c) (cond ((and (eq? (car a) ’hex-number) (char-hex? c)) (unitlist ‘(hex-number . ,(+ (∗ (cdr a) 16) (char-hex→integer/safe c))))) (else mzero list )))) (define parse-dec-digit (λ (a c) (cond ((and (eq? (car a) ’decimal-number) (char-numeric? c)) (unitlist ‘(decimal-number . ,(+ (∗ (cdr a) 10) (− (char→integer c) 48))))) (else mzero list )))) (define parse-alphanumeric (λ (a c) (cond ((and (eq? (car a) ’word-string) (or (char-alphabetic? c) (char-numeric? c))) (unitlist ‘(word-string . ,(string-append (cdr a) (string c))))) (else mzero list )))) Below we produce a legal hex and alphanumeric string. Again, the hex string has been converted to the decimal number, 171. > (bindlist (mplus list (unitlist ’(hex-number . 0)) (unitlist ’(decimal-number . 0)) (unitlist ’(word-string . ""))) (λ (a) (parse-c∗ a (string→list "ab")))) ((hex-number . 171) (word-string . "ab")) Next, we get a legal hex number, decimal number, and alphanumeric string. > (bindlist (mplus list (unitlist ’(hex-number . 0)) (unitlist ’(decimal-number . 0)) (unitlist ’(word-string . ""))) (λ (a) (parse-c∗ a (string→list "123")))) ((hex-number . 291) (decimal-number . 123) (word-string . "123")) Of course, if we discover a special character, we fail by returning the empty list of answers. > (bindlist (mplus list (unitlist ’(hex-number . 0)) (unitlist ’(decimal-number . 0)) (unitlist ’(word-string . ""))) (λ (a) (parse-c∗ a (string→list "abc@x")))) () 14 PARTIAL DRAFT 7 The Maybe Monad Here is the maybe monad. (define unitmaybe (λ (a) ‘(Just ,a))) (define bindmaybe (λ (ma sequel ) (cond ((eq? (car ma) ’Just) (let ((a (cadr ma))) (sequel a))) (else ma)))) A ma in the maybe monad is either a list of the form (Just a) where a is a natural value, or (Nothing). The Just tag means the computation was successful, while Nothing indicates failure. If you have ever used Scheme’s assq, then you know the ill-structured mess of always explicitly checking for failure. The maybe monad allows the programmer to think at a higher level when handling of failure is not relevant. Consider new-assq, which is like assq. Its job is to return (Just a) where a is the cdr of the first pair in p∗ whose car matches v . (define new-assq (λ (v p∗ ) (cond ((null? p∗ ) ’(Nothing)) ; ⇐= (Nothing) is a ma representing failure ((eq? (caar p∗ ) v ) (unitmaybe (cdar p∗ ))) (else (bindmaybe (new-assq v (cdr p∗ )) (λ (a) (unitmaybe a))))))) Since (new-assq v (cdr p∗ )) is a tail call, we can rewrite new-assq relying on η reduction and the first monadic law, leading to (define new-assq (λ (v p∗ ) (cond ((null? p∗ ) ’(Nothing)) ((eq? (caar p∗ ) v ) (unitmaybe (cdar p∗ ))) (else (new-assq v (cdr p∗ )))))) All right-hand sides of each cond-clause must be mas, of course. We see that they are since the only way to terminate is in the first two cond-clauses, and each is a ma. To see how we might use new-assq, we run the following test. > (bindmaybe (let ((ma1 (new-assq 8 ’((7 . 1) (9 . 3))))) (cond ((eq? (car ma1 ) ’Just) ma1 ) (else (let ((ma2 (new-assq 8 ’((9 . 4) (6 . 5) (8 . 2) (7 . 3))))) ma2 )))) (λ (a) (new-assq a ’((1 . 10) (2 . 20))))) (Just 20) We have to verify that the second argument to bindmaybe is a ma. In either clause of the cond expression above, the result is a ma. Here we are looking up 8 in two different association lists. Since 8 is not in the first association list, ma1 is (Nothing), so the first cond clause fails and we try looking up 8 in the other 15 PARTIAL DRAFT association list. This succeeds with (Just 2), so the pure variable a in the sequel gets bound to the pure value 2. We are then taking the pure value 2 and looking it up in a third association list, which returns (Just 20). 8 The Continuation Monad Here is the continuation monad. (define unitcont (λ (a) (λ (k ) ; ⇐= This function is a ma. (k a)))) (define bindcont (λ (ma sequel ) (λ (k ) ; ⇐= This function is a mb (let ((k̂ (λ (a) (let ((mb (sequel a))) (mb k ))))) (ma k̂))))) If we monadify the definition of remberevens Xcountevens cps using the continuation monad, then the definition of remberevens Xcountevens becomes a single argument procedure. (define remberevens Xcountevens (λ (l ) (cond ((null? l ) (unitcont ‘(() . 0))) ((pair? (car l )) (bindcont (remberevens Xcountevens (car l )) (λ (pa) (bindcont (remberevens Xcountevens (cdr l )) (λ (pd ) (unitcont ‘(,(cons (car pa) (car pd )) . ,(+ (cdr pa) (cdr pd ))))))))) ((or (null? (car l )) (odd? (car l ))) (bindcont (remberevens Xcountevens (cdr l )) (λ (p) (unitcont ‘(,(cons (car l ) (car p)) . ,(cdr p)))))) (else (bindcont (remberevens Xcountevens (cdr l )) (λ (p) (unitcont ‘(,(car p) . ,(add1 (cdr p)))))))))) > ((remberevens Xcountevens ’(2 3 (7 4 5 6) 8 (9) 2)) (λ (p) p)) ((3 (7 5) (9)) . 5) This should be enough evidence that our code is in continuation-passing style without an explicit continuation being passed around. We could use a similar derivation that shows how to regain the earlier explicit CPS’d definition, just as we generated store-passing style in the first lecture. We leave that as a tedious exercise for the reader. Notably, the continuation monad allows us to write programs that use something very similar to call/cc, which we will name callcc. Here is its definition. 16 PARTIAL DRAFT (define callcc (λ (f ) (λ (k ) (let ((k-as-proc (λ (a) (λ (k ignored ) (k a))))) (let ((ma (f k-as-proc))) (ma k )))))) In callcc we package the incoming current continuation k in a function that will ignore the future current continuation and invoke the stored k . We call this function k-as-proc, pass it to f , and then pass the current continuation k to the resulting ma. We can demonstrate callcc with a program that takes the same kind of argument as remberevens and immediately returns 0 if a zero is found, otherwise it forms the product of all the numbers in this list. (define product (λ (ls exit) (cond ((null? ls) (unitcont 1)) ((pair? (car ls)) (bindcont (product (car ls) exit) (λ (a) (bindcont (product (cdr ls) exit) (λ (d ) (unitcont (∗ a d ))))))) ((zero? (car ls)) (exit 0)) (else (bindcont (product (cdr ls) exit) (λ (d ) (unitcont (∗ (car ls) d )))))))) The first test below handles the base case where 1 is returned without invoking out. > ((callcc (λ (out) (product ’() out))) (λ (x ) x )) 1 The next example corresponds to Scheme’s (add1 (call/cc (λ (out) (product ’() out)))). We add one to the answer because, when the value is returned by the default continuation, add1 is waiting. > ((bindcont (callcc (λ (out) (product ’() out))) (λ (a) (unitcont (add1 a)))) (λ (x ) x )) 2 The third example shows how the Scheme expression (add1 (call/cc (λ (out) (product ’(5 0 5) out)))) would be translated monadically. Since add1 is in the continuation, out, we end up adding one to zero. > ((bindcont (callcc (λ (out) (product ’(5 0 5) out))) (λ (a) (unitcont (add1 a)))) (λ (x ) x )) 1 Here, since there is no 0 in the list, we get the product of the numbers in the list being returned by invoking the default continuation. > ((callcc (λ (out) (product ’(2 3 (7 4 5 6) 8 (9) 2) out))) (λ (x ) x )) 725760 17 PARTIAL DRAFT This last example behaves the same as this Scheme example. (call/cc (λ (k0 ) ((car (call/cc (λ (k1 ) (k0 (− (call/cc (λ (k2 ) (k1 ‘(,k2 )))) 1))))) 3))) But, monadifying it is a bit tricky. The ((car ) 3) that is in the continuation of k1 has to move to the first sequel , and similarly, the (k0 (−  1)) has to move to the second sequel . > ((callcc (λ (k0 ) (bindcont (callcc (λ (k1 ) (bindcont (callcc (λ (k2 ) (k1 ‘(,k2 )))) (λ (n) (k0 (− n 1)))))) (λ (a) ((car a) 3))))) (λ (x ) x )) 2 18