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 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe