Re: Why doesn't laziness save the day here?

Dale Jordan wrote:
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, ...
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?
The others have already pointed out the problem with the imperative solution, which used the mutation of the global state with the new random seed. Imperative approach is indeed often a problem. There is a simple solution however. In fact, your message already described it. The key phrase is ``the infinite list is produced in finite batches.'' We merely need to define a list-like data structure that matches our intuitions. The complete code follows. All three run functions, run1 through run3, produce a finite result (shown in the comments after the definition). module RList where -- I don't have Mersenne Twistor installed; so I'll use the stdGen... import System.Random import Control.Monad.State data RList m a = RList [a] -- known finite prefix [m [a]] -- a stream of producing actions pullR :: Monad m => RList m a -> m (RList m a) pullR (RList p (x:xs)) = x >>= \p' -> return $ RList (p++p') xs headR :: Monad m => RList m a -> m a headR (RList (x:_) _) = return x headR x = pullR x >>= headR tailR :: Monad m => RList m a -> m (RList m a) tailR (RList (_:xs) ms) = return $ RList xs ms tailR x = pullR x >>= tailR -- appendR doesn't have to have the monadic type. We go for uniformity with -- the headR appendR :: Monad m => RList m a -> RList m a -> m (RList m a) appendR (RList p1 ms1) (RList p2 ms2) = return $ RList p1 (ms1 ++ (return p2):ms2) takeR :: Monad m => Int -> RList m a -> m (RList m a) takeR 0 l = return l takeR n (RList p ms) | length p >= n = return $ RList (take n p) [] takeR n l = pullR l >>= takeR n -- quite inefficient, but short -- Other list library functions can be implemented in terms of head, tail -- the evaluator, so to speak. It is possibly strict, use it at the -- very end toList :: (Functor m, Monad m) => RList m a -> m [a] toList (RList p []) = return p toList (RList p ms) = pullR (RList [] ms) >>= fmap (p ++) . toList -- Dale Jordan's library, slightly re-written -- 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. -- Again, the monadic type is unncessary; given for the sake of -- uniformity iterateR :: Monad m => m [a] -> m (RList m a) iterateR act = return $ RList [] (repeat act) type Rand r a = State r a -- A simple example of a finite action something :: (RandomGen g) => Int -> Int -> Rand g [Int] something n m = sequence . replicate n . State $ randomR (m,m+9) run1 = evalState (toList =<< takeR 10 =<< (iterateR (something 2 0))) $ mkStdGen 42 -- [1,1,7,4,6,1,8,1,8,5] run2 = evalState (toList =<< takeR 10 =<< (iterateR (something 2 0) >> iterateR (something 3 10))) $ mkStdGen 42 -- [11,11,17,14,16,11,18,11,18,15] run3 = evalState (toList =<< (takeR 10 =<< (iterateR (something 2 0) >>= headR >>= iterateR . something 3))) $ mkStdGen 42 -- [8,5,7,2,9,2,9,6,6,10]

oleg@okmij.org wrote:
The others have already pointed out the problem with the imperative solution, which used the mutation of the global state with the new random seed. Imperative approach is indeed often a problem.
As Daniel Fischer pointed out, my immediate problem was that iterateR never finished, even though it did produce results lazily. I missed the subtlety that access to results didn't mean access to the state.
There is a simple solution however. [Snipped ASCII art of head exploding...]
module RList where
[Nice code snipped] So, if I may paraphrase, oleg's solution works by reifying the implicit continuation in my iterateR's recursive definition into a data structure that is explicitly forced with pullR and its callers. Fascinating... Thanks to all who responded. Dale
participants (2)
-
Dale Jordan
-
oleg@okmij.org