How do I do conditional tail recursion in a monad?

Hi, I would like to write a function untilM, which would be to until as mapM is to map. An example use would be if I had a function dice :: State Int Int which returns random dice throws within a state monad. Then I'd like to be able to do something like untilM (\(s,p)-> s>=100) f (0,1) where f (s,p) = do d <- dice return (s+d, p*d) This should throw dice until the sum exceeds 100, and keeping track of the product as we go along. The problem is that I get stuck trying to manage the interaction of the conditional and the recursion in untilM. Let's start with until: until p f x = if p x then x else until p f (f x) So I figure untilM should look something like: untilM :: Monad m => (a -> Bool) -> (a -> m a) -> a -> m a untilM p f x = return (if p x then x else untilM p f (f x)) The problem is that the two branches of the conditional have different types. If I try to remedy that by changing "then x" to "then return x", it still isn't happy. (My real question is, how do I do conditional tail recursion in a monad?) Thanks in advance.

DavidA wrote:
So I figure untilM should look something like: untilM :: Monad m => (a -> Bool) -> (a -> m a) -> a -> m a untilM p f x = return (if p x then x else untilM p f (f x)) The problem is that the two branches of the conditional have different types. If I try to remedy that by changing "then x" to "then return x", it still isn't happy.
You are applying return to the result of untilM. This makes a m (m a). The following is closer: *Main> :t let untilM p f x = if p x then return x else untilM p f (f x) in untilM let untilM p f x = if p x then return x else untilM p f (f x) in untilM :: (Monad m) => (a -> Bool) -> (a -> a) -> a -> m a ...but here 'f' is a pure function, not a monadic action. If you want f to be a monadic action then you want: *Main> :t let untilM p f x = if p x then return x else untilM p f =<< f x in untilM let untilM p f x = if p x then return x else untilM p f =<< f x in untilM :: (Monad m) => (a -> Bool) -> (a -> m a) -> a -> m a (if you prefer do notation to explicit binds, rewrite "untilM p f =<< f x" as "y <- f x ; untilM p f y")
(My real question is, how do I do conditional tail recursion in a monad?)
actually I don't think that was your real question :) Your real question was about conditional recursion in monads, but had nothing to do with tailness or otherwise. Tail recursion is a concept which has implementation relevance in an eager language, but is often a red-herring in a lazy language. Jules

Interesting, but what if 'p' is also a monadic action? For instance, it might access the state of the State monad which 'f' is updating. On Mar 21, 2007, at 5:31 AM, Jules Bean wrote:
..but here 'f' is a pure function, not a monadic action. If you want f to be a monadic action then you want:
*Main> :t let untilM p f x = if p x then return x else untilM p f =<< f x in untilM let untilM p f x = if p x then return x else untilM p f =<< f x in untilM :: (Monad m) => (a -> Bool) -> (a -> m a) -> a -> m a
___________________ (---o-------o-o-o---o-o-o----( David F. Place mailto:d@vidplace.com

David F. Place wrote:
Interesting, but what if 'p' is also a monadic action? For instance, it might access the state of the State monad which 'f' is updating.
Then I'd stop trying to do it as a one-liner, I suspect: let untilM p f x = do cond <- p x if cond then return x else do y <- f x untilM p f y
On Mar 21, 2007, at 5:31 AM, Jules Bean wrote:
..but here 'f' is a pure function, not a monadic action. If you want f to be a monadic action then you want:
*Main> :t let untilM p f x = if p x then return x else untilM p f =<< f x in untilM let untilM p f x = if p x then return x else untilM p f =<< f x in untilM :: (Monad m) => (a -> Bool) -> (a -> m a) -> a -> m a
___________________ (---o-------o-o-o---o-o-o----( David F. Place mailto:d@vidplace.com

So, the next question is: Why isn't this already in Control.Monad? On Mar 21, 2007, at 8:27 AM, Jules Bean wrote:
David F. Place wrote:
Interesting, but what if 'p' is also a monadic action? For instance, it might access the state of the State monad which 'f' is updating.
Then I'd stop trying to do it as a one-liner, I suspect:
let untilM p f x = do cond <- p x if cond then return x else do y <- f x untilM p f y
On Mar 21, 2007, at 5:31 AM, Jules Bean wrote:
..but here 'f' is a pure function, not a monadic action. If you want f to be a monadic action then you want:
*Main> :t let untilM p f x = if p x then return x else untilM p f =<< f x in untilM let untilM p f x = if p x then return x else untilM p f =<< f x in untilM :: (Monad m) => (a -> Bool) -> (a -> m a) -> a -> m a
___________________ (---o-------o-o-o---o-o-o----( David F. Place mailto:d@vidplace.com
___________________ (---o-------o-o-o---o-o-o----( David F. Place mailto:d@vidplace.com

David F. Place wrote:
So, the next question is: Why isn't this already in Control.Monad?
Some people have proposed it. Part of the reason is all the possible variations (monadic action, monadic test, monadic filter, etc etc), and it's all really very easy to write yourself. Perhaps it's even *enlightening* to write it yourself sometimes, since it gives you practice in writing monadic code and understanding these points :) Maybe another part of the reason is that supplying people with a fixed list of 'imperative-style' combinators makes them think that that's all there is, and struggle when they need something more complex because they aren't really sure how to use the 'lower-level' building blocks. Still, I think there is still room for someone to suggest a really top-notch list of 'imperative-style-monadic' combinators. Jules

On Mar 21, 2007, at 8:40 AM, Jules Bean wrote:
Part of the reason is all the possible variations (monadic action, monadic test, monadic filter, etc etc), and it's all really very easy to write yourself.
Indeed, I had just written whileM_ p a = do cond <- p ; if cond then do a ; whileM_ p a else return () I always wonder, when I have to do such things, if I just haven't studied the libraries well enough. ___________________ (---o-------o-o-o---o-o-o----( David F. Place mailto:d@vidplace.com

These sort of things come up from time to time. Why not make a proposal? http://www.haskell.org/pipermail/haskell-cafe/2006-February/014214.html Dominic.

I suppose there are plenty of flavors for such functions, and they are
simple enough to write.
One I've been using a bit is this one:
loopM :: Monad m => a -> (a -> m (Maybe a)) -> m ()
loopM start action = loop start
where
loop i =
do result <- action i
case result of
Nothing -> return ()
Just newval -> loop newval
BTW: what is considered better? The above or this one:
loopM :: Monad m => a -> (a -> m (Maybe a)) -> m ()
loopM i action =
do result <- action i
case result of
Nothing -> return ()
Just newval -> loopM newval action
Or is there no difference at all? Sorry for the non-sequitur here.
Usage example:
streamToFile :: Storable a => [a] -> String -> IO ()
streamToFile list fname =
do let elementSize = sizeOf (head list)
let numElements = (65535 + elementSize) `div` elementSize
let bufferSize = numElements * elementSize
f <- openBinaryFile fname WriteMode
allocaArray bufferSize $ \buf ->
loopM list $ \list ->
do let (cur, next) = splitAt numElements list
pokeArray buf cur
hPutBuf f buf (length cur * elementSize)
case next of
[] -> return Nothing
otherwise -> return (Just next)
hClose f
(allows writing a lazy list to a binary file)
JCAB
On Wed, 21 Mar 2007 13:34:48 -0700, Dominic Steinitz
These sort of things come up from time to time. Why not make a proposal?
http://www.haskell.org/pipermail/haskell-cafe/2006-February/014214.html
Dominic.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

DavidA wrote:
I would like to write a function untilM, which would be to until as mapM is to map.
An example use would be if I had a function dice :: State Int Int which returns random dice throws within a state monad.
Then I'd like to be able to do something like untilM (\(s,p)-> s>=100) f (0,1) where f (s,p) = do d <- dice return (s+d, p*d) This should throw dice until the sum exceeds 100, and keeping track of the product as we go along.
How about going with an infinite list of random numbers with no monads involved head . dropUntil ((>= 100) . fst) . scanl' (\(s,p) d -> (d+s,p*d)) (0,1) . randomRs (1,6) Of course, this has the drawback that you cannot take further random numbers afterwards. Regards, apfelmus
participants (6)
-
apfelmus
-
David F. Place
-
DavidA
-
Dominic Steinitz
-
Juan Carlos Arevalo Baeza
-
Jules Bean