
I've seen comments in various places that monads allow you to "borrow things from the future". That sounds completely absurd to me... can anybody explain?

On 8/17/07, Andrew Coppin
I've seen comments in various places that monads allow you to "borrow things from the future".
That sounds completely absurd to me... can anybody explain?
Suppose you buy into the notion that monads sequence actions. Then consider the following code:
import Control.Monad.State
test = do put $ x+1 x <- return 1 return undefined
go = execState test undefined
execState runs a sequence of actions in the state monad, ignoring the returned value and simply giving you back the resulting state. So work through what this code does: It sets the value of the state to be 1+x. It then sets x to be 1. And then it returns undefined. We don't care about the return value, we just care about the state. And clearly the state is 2. But if you believe all that action sequencing stuff, we set the state using x before we actually set the value of x. So we're reading from the future. But you can breathe a sigh of relief because the above code doesn't compile and the laws of physics remain unharmed. Except...you can switch on ghc's special time travel features using the -fglasgow-exts flag. Use the time-travel compatible mdo instead of do and you'll find that this compiles and runs fine:
import Control.Monad.State import Control.Monad.Fix
test = mdo put $ x+1 x <- return 1 return undefined
go = execState test undefined -- Dan

On 8/17/07, Dan Piponi
On 8/17/07, Andrew Coppin
wrote: That sounds completely absurd to me... can anybody explain? Except...you can switch on ghc's special time travel features...
On reflection I decided my example isn't very convincing. For one thing, I've argued in another thread that monads aren't really about sequencing actions. But I concede that there is an exception: the IO monad. Because the IO monad has observable side effects you can actually see whether or not an action has taken place at a particular time, so it really does have to sequence actions. So now consider the following code:
import IO import Control.Monad.Fix
test = mdo z <- return $ x+y print "Hello" x <- readLn y <- readLn return z
Evaluate test and you'll be prompted to enter a pair of numbers. You'll then be rewarded with their sum. But the "Hello" message is printed before the prompt for input so we know that's being executed first. And we can see clearly that the summation is performed before the "Hello" message. So clearly this program is computing its result before receiving the input. At this point your natural reaction should be to replace 'print "Hello"' with 'print z'... -- Dan

Dan Piponi wrote:
On 8/17/07, Dan Piponi
wrote: On 8/17/07, Andrew Coppin
wrote: That sounds completely absurd to me... can anybody explain?
Except...you can switch on ghc's special time travel features...
On reflection I decided my example isn't very convincing. For one thing, I've argued in another thread that monads aren't really about sequencing actions. But I concede that there is an exception: the IO monad. Because the IO monad has observable side effects you can actually see whether or not an action has taken place at a particular time, so it really does have to sequence actions. So now consider the following code:
import IO import Control.Monad.Fix
test = mdo z <- return $ x+y print "Hello" x <- readLn y <- readLn return z
Evaluate test and you'll be prompted to enter a pair of numbers. You'll then be rewarded with their sum. But the "Hello" message is printed before the prompt for input so we know that's being executed first. And we can see clearly that the summation is performed before the "Hello" message. So clearly this program is computing its result before receiving the input.
At this point your natural reaction should be to replace 'print "Hello"' with 'print z'...
Surely all this means is that the magical "mdo" keyword makes the compiler arbitrarily reorder the expression...?

Andrew Coppin wrote:
Surely all this means is that the magical "mdo" keyword makes the compiler arbitrarily reorder the expression...?
It is not magical but simple syntactic sugar. And no, the compiler does not 'arbitrarily reorder' anything, you do the same in any imperative language with pointers/references and mutation.
From the ghc manual:
----------- 7.3.3. The recursive do-notation ... The do-notation of Haskell does not allow recursive bindings, that is, the variables bound in a do-expression are visible only in the textually following code block. Compare this to a let-expression, where bound variables are visible in the entire binding group. It turns out that several applications can benefit from recursive bindings in the do-notation, and this extension provides the necessary syntactic support. Here is a simple (yet contrived) example: import Control.Monad.Fix justOnes = mdo xs <- Just (1:xs) return xs As you can guess justOnes will evaluate to Just [1,1,1,.... The Control.Monad.Fix library introduces the MonadFix class. It's definition is: class Monad m => MonadFix m where mfix :: (a -> m a) -> m a ----------- It is unfortunate that the manual does not give the translation rules, or at least the translation for the given example. If I understood things correctly, the example is translated to justOnes = mfix (\xs' -> do { xs <- Just (1:xs'); return xs } You can imagine what happens operationally by thinking of variables as pointers. As long as you don't de-reference them, you can use such pointers in expressions and statements even if the object behind them has not yet been initialized (=is undefined). The question is how the objects are eventually be initialized. In imperative languages this is done by mutation. In Haskell you employ lazy evaluation: the art of circular programming is to use not-yet-defined variables lazily, that is, you must never demand the object before the mdo block has been executed. A good example is http://www.cse.ogi.edu/PacSoft/projects/rmb/doubly.html which explains how to create a doubly linked circular list using mdo. Cheers Ben

| >From the ghc manual: | | ----------- | 7.3.3. The recursive do-notation | ... | | It is unfortunate that the manual does not give the translation rules, or at | least the translation for the given example. Hmm. OK. I've improved the manual with a URL to the main paper http://citeseer.ist.psu.edu/erk02recursive.html which is highly readable. And I've given the translation for the example as you suggest Simon

Simon Peyton-Jones wrote:
| It is unfortunate that the [ghc] manual does not give the translation rules, or at | least the translation for the given example.
Hmm. OK. I've improved the manual with a URL to the main paper http://citeseer.ist.psu.edu/erk02recursive.html which is highly readable. And I've given the translation for the example as you suggest
Cool, thanks. BTW, the Haskell' wiki says its adoption status is 'probably no' which I find unfortunate. IMHO recursive do is a /very/ useful and practical feature and the cons listed on http://hackage.haskell.org/trac/haskell-prime/wiki/RecursiveDo don't weigh enough against that. Ok, just my (relatively uninformed) 2 cents. Cheers Ben

Benjamin Franksen wrote:
Simon Peyton-Jones wrote:
| It is unfortunate that the [ghc] manual does not give the translation rules, or at | least the translation for the given example.
Hmm. OK. I've improved the manual with a URL to the main paper http://citeseer.ist.psu.edu/erk02recursive.html which is highly readable. And I've given the translation for the example as you suggest
Cool, thanks.
BTW, the Haskell' wiki says its adoption status is 'probably no' which I find unfortunate. IMHO recursive do is a /very/ useful and practical feature and the cons listed on http://hackage.haskell.org/trac/haskell-prime/wiki/RecursiveDo don't weigh enough against that. Ok, just my (relatively uninformed) 2 cents.
Cheers Ben
I will assume that the current compilers will keep the current "mdo" desugaring. It is incredibly valuable, and I use it in two different monad stacks in the regex-tdfa package I released. It has been an implemented extension for quite several version of GHC, and with the separate "mdo" keyword it does not interfere with other code. Why have a lazy language with added monad "do" sugaring support and balk at adding such a well tested and deployed way to use sugar for combining laziness and monads? Toy there g is an identity monadic version of f and h shows the kind of logic I tend to intersperse in an mdo block:
module Main where
import Control.Monad.Fix import Control.Monad.Identity import Control.Monad.Writer
f x = do let a = x*b b = x+1 return a
test_f = runIdentity (f 2) -- 6
g x = mdo a <- return (x*b) b <- return (x+1) return a
test_g = runIdentity (g 2) -- 6
h x = mdo a <- return (x*b) if even b then tell [('a',a)] else return () b <- return (x+1) tell [('b',b)] return a
test_h1 = (runWriter (h 1)) -- (2,[('a',2),('b',2)]) test_h2 = (runWriter (h 2)) -- (6,[('b',3)])
-- Chris

Simon Peyton-Jones wrote:
| >From the ghc manual: | | ----------- | 7.3.3. The recursive do-notation | ...
| | It is unfortunate that the manual does not give the translation rules, or at | least the translation for the given example.
Hmm. OK. I've improved the manual with a URL to the main paper http://citeseer.ist.psu.edu/erk02recursive.html which is highly readable. And I've given the translation for the example as you suggest
After finally reading the paper I agree that repeating the translation in teh manual is not a good idea. However, I suggest the manual should mention the restrictions imposed for mdo (wrt the normal do) * no shadowing allowed for generator bound variables * let bindings must be monomorphic Both of them might cause confusion if someone hits them by accident and starts to wonder what's wrong with her code, in which case it would be helpful if this information were directly available in teh manual. No need to give a detailed rationale (that's what the paper can be read for), just say that they are there. BTW, I agree with the paper that the restrictions are sensible and typically don't hurt. Thanks Ben

On 8/18/07, Andrew Coppin
Surely all this means is that the magical "mdo" keyword makes the compiler arbitrarily reorder the expression...?
What mdo actually does is described here: http://www.cse.ogi.edu/PacSoft/projects/rmb/mdo.pdf My last example desugars to: test = mfix ( \ ~(x,y,z,v) -> do z <- return $ x+y print "Hello" x <- readLn y <- readLn v <- return z return (x,y,z,v)) >>= \(x,y,z,v) -> return v So at core there really is a do-expression that's passing 'return $ x+y' into a print which in turn is passed into the 'readLn's. -- Dan

Hi Dan,
import Control.Monad.State
test = do put $ x+1 x <- return 1 return undefined
go = execState test undefined
I'd just like to point out that you can do something similar without mdo. For example, you can define a monad with newVar, readVar, and writeVar such that running the following results in 2. test = do x <- newVar y <- newVar valx <- readVar x writeVar y (valx+1) writeVar x 1 valy <- readVar y return valy (As you probably know, the previous two Monad.Reader issues include two different examples -- assembler and circuit description -- of circular programming in a monad.) Matt.

Andrew Coppin writes:
I've seen comments in various places that monads allow you to "borrow things from the future".
That sounds completely absurd to me... can anybody explain?
Actually, "borrowing from the future" - in an interpretation which is close to my own interests - doesn't need monads, but *laziness*. If you find this absurd, I propose that you have a look on something a bit light, my paper on a quite crazy way to compute PI with a high precision. The algorithm (not mine, but of Bailey, Borwein and Plouffe) is a masterpiece of numerical math, but its implementation relies on a mad borrowing from the future. http://users.info.unicaen.fr/~karczma/arpap/lazypi.pdf If you don't choke, try another one, the reverse automatic differentiation algorithm, implemented using a variant of the Wadler's "counter-temporal" state monad. http://users.info.unicaen.fr/~karczma/arpap/revdf1.pdf It is quite serious, although inefficient, and has some affinities to the lazy processing of inherited attributes during parsing. More recently, Barak Pearlmutter and Jeff Siskind worked on similar issues, but I am not sure whether they submitted something ready for the audience. Please check it out. Jerzy Karczmarczuk

jerzy.karczmarczuk@info.unicaen.fr wrote:
Andrew Coppin writes:
I've seen comments in various places that monads allow you to "borrow things from the future". That sounds completely absurd to me... can anybody explain?
Actually, "borrowing from the future" - in an interpretation which is close to my own interests - doesn't need monads, but *laziness*.
While this is true, the "mdo" and associated MonadFix class do implement it in a monadic framework where you can write things like mdo x <- f y y <- g x If you interpret do-notation as equivalent to imperative programming then this does indeed look like time travel. Under the covers its more equivalent to let x = f y y = g x which is also known as "tying the knot" or the "credit card transform" (both keywords worth looking up). However I can't say I really have my head around it properly. Paul.
participants (8)
-
Andrew Coppin
-
Benjamin Franksen
-
ChrisK
-
Dan Piponi
-
jerzy.karczmarczuk@info.unicaen.fr
-
Matthew Naylor
-
Paul Johnson
-
Simon Peyton-Jones