
Hi all, I was wondering if any of you knew whether the following was possible, (I discussed this a little on #haskell at the weekend but didn't quite get to the bottom of it): Say I have a monadic action:
f :: a -> m a
and an initial value of type a. I'd like to iterate this action and collect the results of each iteration in a list, as with 'iterate' on normal functions:
iterate (>>= f) . return $ a
However, I would also like to memoize the intermediate results of the iteration, such that the entire iteration runs in O(n) time rather than O(n^2). This also implies a slight semantic difference, as side-effecting or non-deterministic actions will not be repeated in each iteration, while maintaining the laziness of the iteration function. Is it possible to do this? Many thanks, Tim

On Mon, Aug 15, 2011 at 09:00:19AM +0100, Tim Cowlishaw wrote:
Hi all,
I was wondering if any of you knew whether the following was possible, (I discussed this a little on #haskell at the weekend but didn't quite get to the bottom of it):
Say I have a monadic action:
f :: a -> m a
and an initial value of type a.
I'd like to iterate this action and collect the results of each iteration in a list, as with 'iterate' on normal functions:
iterate (>>= f) . return $ a
However, I would also like to memoize the intermediate results of the iteration, such that the entire iteration runs in O(n) time rather than O(n^2). This also implies a slight semantic difference, as side-effecting or non-deterministic actions will not be repeated in each iteration, while maintaining the laziness of the iteration function. Is it possible to do this?
How about this? iterateM :: Monad m => (a -> m a) -> a -> m [a] iterateM f a = (a:) `liftM` (f a >>= iterateM f) -Brent

Brent Yorgey
How about this?
iterateM :: Monad m => (a -> m a) -> a -> m [a] iterateM f a = (a:) `liftM` (f a >>= iterateM f)
-Brent
The problem with this is that it is not "lazy" in the sense that inc :: Int -> IO Int inc x = (print x) >> return $! x + 1 main = do xs <- liftM (take 5) $ iterateM inc 0 print xs will never terminate. It will keep printing all natural numbers but it will never print the list xs. I don't quite understand why this is so, nor do I know how to rewrite iterateM to get the desired behavior. But I wish someone would enlighten me :-)

On Sat, Jan 28, 2012 at 8:12 PM, Alex
Brent Yorgey
writes: iterateM :: Monad m => (a -> m a) -> a -> m [a] iterateM f a = (a:) `liftM` (f a >>= iterateM f) The problem with this is that it is not "lazy" in the sense that
[IO example]
What do you mean it's not lazy ? look :
import Control.Monad import Control.Monad.State.Lazy
inc x = modify (+x) >> get
main = do let (pows,_) = runState (liftM (take 5) $ iterateM inc 1) $ 0 print pows
.... In other words, the lazyness is not in iterateM, it's in the monad (you can use unsafeInterleaveIO to get lazy IO but that's... unsafe).
will never terminate. It will keep printing all natural numbers but it will never print the list xs. I don't quite understand why this is so, nor do I know how to rewrite iterateM to get the desired behavior. But I wish someone would enlighten me :-)
Basically IO is strict, if it wasn't, you wouldn't always get the correct order for your side-effects except when explicit data dependency forced it (unsafeInterleaveIO is a way to relax this when you don't care exactly when your side-effect happens, for instance lazy IO take the stance that you don't need to know exactly when your file will be read, so you might as well defer its reading until the content is really needed). -- Jedaï
participants (4)
-
Alex
-
Brent Yorgey
-
Chaddaï Fouché
-
Tim Cowlishaw