Why doesn't laziness save the day here?

Kind and Generous Haskellers: I am ensnared in a briar patch of infinite lists and Random gnerators trying to use laziness to advantage. Here's my code: ----------------- 8< -------------------- import Control.Applicative import Control.Monad import Control.Monad.Random import Control.Monad.State import System.Random.Mersenne.Pure64 -- Specialized iterator for running actions in Rand monad, to thread -- the generator. The idea is that the action returns a finite list -- of random values and iterateR lazily creates an infinite list of -- values. iterateR act = do gen <- get let (as,gen') = runRand act gen put $! gen' (as ++) <$> iterateR act -- A simple example of a finite action something :: (RandomGen g) => Int -> Int -> Rand g [Int] something n m = sequence . replicate n $ getRandomR (m,m+9) run1 = evalState (take 10 <$> (iterateR (something 2 0))) $ pureMT 42 run2 = evalState (take 10 <$> (iterateR (something 2 0) >> iterateR (something 3 10))) $ pureMT 42 run3 = evalState (take 10 <$> (iterateR (something 2 0) >>= iterateR . (something 3 . head))) $ pureMT 42 ------------------- >8 ---------------------- Evaluating run1 works fine (ghci 10.3): *Main> run1 [1,9,5,3,6,9,1,5,1,8] Evaluating run2 or run3 loops and quickly exhausts the heap. (Using Control.Monad.State.Strict causes stack overflow, though) The motivation for iterateR is to be able to have the ultimate consumer determine how many random values to force, but still have a single random generator used throughout the computation. My intuition tells me that since the infinite list is produced in finite batches, the generator shouldn't be tangled up in an infinite list such as produced by MonadRandom's getRandoms, but I only have a pink belt in Haskell-fu. Can anyone explain why this is looping or point out a better way to generate an arbitrary-length random list while still being able to reuse the generator? (I'd rather not use split since this generator doesn't support it and its of dubious soundness.) Dale Jordan

Am Dienstag 05 Januar 2010 02:31:20 schrieb Dale Jordan:
Kind and Generous Haskellers:
I am ensnared in a briar patch of infinite lists and Random gnerators trying to use laziness to advantage. Here's my code:
----------------- 8< -------------------- import Control.Applicative import Control.Monad import Control.Monad.Random import Control.Monad.State import System.Random.Mersenne.Pure64
-- Specialized iterator for running actions in Rand monad, to thread -- the generator. The idea is that the action returns a finite list -- of random values and iterateR lazily creates an infinite list of -- values.
iterateR act = do gen <- get let (as,gen') = runRand act gen put $! gen' (as ++) <$> iterateR act
-- A simple example of a finite action something :: (RandomGen g) => Int -> Int -> Rand g [Int] something n m = sequence . replicate n $ getRandomR (m,m+9)
run1 = evalState (take 10 <$> (iterateR (something 2 0))) $ pureMT 42
run2 = evalState (take 10 <$> (iterateR (something 2 0) >> iterateR (something 3 10))) $ pureMT 42
run3 = evalState (take 10 <$> (iterateR (something 2 0) >>= iterateR . (something 3 . head))) $ pureMT 42 ------------------- >8 ----------------------
Evaluating run1 works fine (ghci 10.3): *Main> run1 [1,9,5,3,6,9,1,5,1,8]
Evaluating run2 or run3 loops and quickly exhausts the heap.
(Using Control.Monad.State.Strict causes stack overflow, though)
The motivation for iterateR is to be able to have the ultimate consumer determine how many random values to force, but still have a single random generator used throughout the computation.
My intuition tells me that since the infinite list is produced in finite batches, the generator shouldn't be tangled up in an infinite list such as produced by MonadRandom's getRandoms, but I only have a pink belt in Haskell-fu.
Can anyone explain why this is looping
Rand g is basically State g (or, rather StateT g Identity). Looking at the definition of (>>=) for that: instance (Monad m) => Monad (StateT s m) where return a = StateT $ \s -> return (a, s) m >>= k = StateT $ \s -> do ~(a, s') <- runStateT m s runStateT (k a) s' in a1 >> a2, if a2 wants to use the state, it can't do that before a1 is done. iterateR is never finished, so iterateR act >> otherAct can only work if otherAct doesn't use the state (or puts a state before using it).
or point out a better way to generate an arbitrary-length random list while still being able to reuse the generator?
Sorry, no.
(I'd rather not use split since this generator doesn't support it and its of dubious soundness.)
Dale Jordan

On Mon, Jan 4, 2010 at 6:31 PM, Dale Jordan
Can anyone explain why this is looping or point out a better way to generate an arbitrary-length random list while still being able to reuse the generator? (I'd rather not use split since this generator doesn't support it and its of dubious soundness.)
Well there is more than one way to split. You don't have to split the generator -- if you act on a stream of random numbers, you can split the stream also: split :: [a] -> ([a],[a]) split (x:xs) = (x:bs,as) where (as,bs) = split xs However too much splitting in this case causes a performance penalty, since you start discarding large portions of the stream. If you don't want to split the generator, this is the only way I can think of that is deterministic in the random seed. If determinism is not required, as many times it is not with *random* computations, you can use the value-supply package on hackage, which uses a bit of unsafePerformIO magic to turn a serial stream into a splittable stream. But you lose composable repeatability. Luke

2010/1/5 Dale Jordan
The motivation for iterateR is to be able to have the ultimate consumer determine how many random values to force, but still have a single random generator used throughout the computation.
Hi Dale If you want the producer and consumer to run at different speeds with something in-between to synchronize them (velomorphisms anyone?), you might want to look at Jeremy Gibbons's spigot algorithm for pi and also his metamorphisms paper. http://www.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/spigot.pdf http://www.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/metamorphis... That said, I've personally found it hard to frame code in the spigot style so I couldn't readily offer any tips on the code you've presented. Best wishes Stephen
participants (4)
-
Dale Jordan
-
Daniel Fischer
-
Luke Palmer
-
Stephen Tetley