Difference between revisions of "New monads/MonadRandomSplittable"

From HaskellWiki
Jump to navigation Jump to search
(The use case that led me to reinvent this monad)
(The infinite random tree example now compiles without extra code)
Line 82: Line 82:
   
 
<haskell>
 
<haskell>
  +
data Tree a = Branch a (Tree a) (Tree a) | Leaf deriving (Eq, Show)
makeRandomTree = do this <- randomNode
 
  +
left <- split $ randomLeftChild this
 
 
makeRandomTree = do
right <- split $ randomRightChild this
 
  +
this <- getRandomR (0,9)
return $ Node this left right
 
  +
left <- splitRandom makeRandomTree
  +
right <- splitRandom makeRandomTree
 
return $ Branch this left right
 
</haskell>
 
</haskell>
 
By removing the RNG-dependencies, infinite random data structures can be constructed lazily.
 
By removing the RNG-dependencies, infinite random data structures can be constructed lazily.
  +
  +
And for completeness the non-monadic version:
  +
<haskell>
  +
randomTree g = Branch a (randomTree gl) (randomTree gr)
  +
where
  +
(a, g') = randomR (0, 9) g
  +
(gl, gr)= split g'
  +
</haskell>
  +
Note that the monadic version needs one split operation more, so yields different results.

Revision as of 22:44, 18 November 2006


When using New monads/MonadRandom, one may also want to use a MonadRandom equivalent of RandomGen's split function:

class (MonadRandom m) => MonadRandomSplittable m where
    splitRandom :: m a -> m a

instance (Monad m, RandomGen g) => MonadRandomSplittable (RandomT g m) where
    splitRandom ma  = (RandomT . liftState) split >>= lift . evalRandomT ma

MonadRandomSplittable can then be derived for Rand by GHC:

newtype Rand g a = Rand { unRand :: RandomT g Identity a }
    deriving (Functor, Monad, MonadRandom, MonadRandomSplittable)

Example of usage

test   :: Rand StdGen [Bool] -> (Int, [Bool], Int)
test ma = evalRand (liftM3 (,,) (getRandomR (0,99)) ma (getRandomR (0,99)))
                (mkStdGen 0)

Then

*MonadRandom> test (replicateM 0 getRandom)
(45,[],55)
*MonadRandom> test (replicateM 2 getRandom)
(45,[True,True],0)

*MonadRandom> test (splitRandom $ replicateM 0 getRandom)
(45,[],16)
*MonadRandom> test (splitRandom $ replicateM 2 getRandom)
(45,[False,True],16)

*MonadRandom> case test undefined of (a,_,c) -> (a,c)
*** Exception: Prelude.undefined
*MonadRandom> case test (splitRandom undefined) of (a,_,c) -> (a,c)
(45,16)

Laws

It is not clear to me exactly what laws splitRandom should satisfy, besides monadic variations of the "split laws" from the Haskell Library Report

For all terminating ma and mb, it should hold that

  liftM3 (\a _ c -> (a,c)) getRandom ma getRandom === liftM3 (\a _ c -> (a,c)) getRandom mb getRandom

For monad transformers, it would also be nice if

splitRandom undefined === splitRandom (return ()) >> lift undefined

For example,

>runIdentity $ runRandomT (splitRandom (return ()) >> lift undefined >> return ()) (mkStdGen 0)
((),40014 2147483398)
>runIdentity $ runRandomT (splitRandom undefined >> return ()) (mkStdGen 0)
((),40014 2147483398)

But

>runRandomT (splitRandom (return ()) >> lift undefined >> return ()) (mkStdGen 0)
*** Exception: Prelude.undefined
>runRandomT (splitRandom undefined >> return ()) (mkStdGen 0)
*** Exception: Prelude.undefined

I have no idea how to express this idea for monads that aren't transformers though. But for Rand it means that:

>runRand (splitRandom undefined >> return ()) (mkStdGen 0)
((),40014 2147483398)

Why?

In replicateM 100 (splitRandom expensiveAction) There are no RNG-dependencies between the different expensiveActions, so they may be computed in parallel.

data Tree a = Branch a (Tree a) (Tree a) | Leaf deriving (Eq, Show)

makeRandomTree  = do
    this  <- getRandomR (0,9)
    left  <- splitRandom makeRandomTree
    right <- splitRandom makeRandomTree
    return $ Branch this left right

By removing the RNG-dependencies, infinite random data structures can be constructed lazily.

And for completeness the non-monadic version:

randomTree g    = Branch a (randomTree gl) (randomTree gr)
    where
        (a, g') = randomR (0, 9) g
        (gl, gr)= split g'

Note that the monadic version needs one split operation more, so yields different results.